diff --git a/main/Main.hs b/main/Main.hs index 3f26a470..f67fd501 100644 --- a/main/Main.hs +++ b/main/Main.hs @@ -15,6 +15,7 @@ import qualified Data.Text.IO as TextIO (getContents, hPutStr, putStr) import Data.Version (showVersion) import GHC.IO.Encoding (utf8) import qualified Nixfmt +import Nixfmt.Predoc (layout) import Paths_nixfmt (version) import System.Console.CmdArgs ( Data, @@ -44,6 +45,7 @@ data Nixfmt = Nixfmt width :: Width, check :: Bool, quiet :: Bool, + strict :: Bool, verify :: Bool, ast :: Bool } @@ -64,6 +66,7 @@ options = &= help (addDefaultHint defaultWidth "Maximum width in characters"), check = False &= help "Check whether files are formatted without modifying them", quiet = False &= help "Do not report errors", + strict = False &= help "Enable a stricter formatting mode that isn't influenced as much by how the input is formatted", verify = False &= help @@ -140,8 +143,8 @@ type Formatter = FilePath -> Text -> Either String Text toFormatter :: Nixfmt -> Formatter toFormatter Nixfmt{ast = True} = Nixfmt.printAst -toFormatter Nixfmt{width, verify = True} = Nixfmt.formatVerify width -toFormatter Nixfmt{width, verify = False} = Nixfmt.format width +toFormatter Nixfmt{width, verify = True, strict} = Nixfmt.formatVerify (layout width strict) +toFormatter Nixfmt{width, verify = False, strict} = Nixfmt.format (layout width strict) type Operation = Formatter -> Target -> IO Result diff --git a/src/Nixfmt.hs b/src/Nixfmt.hs index 62590d1f..fd432a6d 100644 --- a/src/Nixfmt.hs +++ b/src/Nixfmt.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE RankNTypes #-} + module Nixfmt ( errorBundlePretty, ParseErrorBundle, @@ -13,9 +15,9 @@ import Data.Either (fromRight) import Data.Text (Text, unpack) import Data.Text.Lazy (toStrict) import qualified Nixfmt.Parser as Parser -import Nixfmt.Predoc (layout) +import Nixfmt.Predoc (Pretty) import Nixfmt.Pretty () -import Nixfmt.Types (Expression, ParseErrorBundle, Whole (..), walkSubprograms) +import Nixfmt.Types (Expression, LanguageElement, ParseErrorBundle, Whole (..), walkSubprograms) import qualified Text.Megaparsec as Megaparsec (parse) import Text.Megaparsec.Error (errorBundlePretty) import Text.Pretty.Simple (pShow) @@ -23,13 +25,14 @@ import Text.Pretty.Simple (pShow) -- import Debug.Trace (traceShow, traceShowId) type Width = Int +type Layouter = forall a. (Pretty a, LanguageElement a) => a -> Text -- | @format w filename source@ returns either a parsing error specifying a -- failure in @filename@ or a formatted version of @source@ with a maximum width -- of @w@ columns where possible. -format :: Width -> FilePath -> Text -> Either String Text -format width filename = - bimap errorBundlePretty (layout width) +format :: Layouter -> FilePath -> Text -> Either String Text +format layout filename = + bimap errorBundlePretty layout . Megaparsec.parse Parser.file filename -- | Pretty print the internal AST for debugging @@ -44,21 +47,21 @@ printAst path unformatted = do -- -- If any issues are found, the operation will fail and print an error message. It will contain a diff showcasing -- the issue on an automatically minimized example based on the input. -formatVerify :: Width -> FilePath -> Text -> Either String Text -formatVerify width path unformatted = do +formatVerify :: Layouter -> FilePath -> Text -> Either String Text +formatVerify layout path unformatted = do unformattedParsed@(Whole unformattedParsed' _) <- parse unformatted - let formattedOnce = layout width unformattedParsed + let formattedOnce = layout unformattedParsed formattedOnceParsed <- first (\x -> pleaseReport "Fails to parse after formatting.\n" <> x <> "\n\nAfter Formatting:\n" <> unpack formattedOnce) (parse formattedOnce) - let formattedTwice = layout width formattedOnceParsed + let formattedTwice = layout formattedOnceParsed if formattedOnceParsed /= unformattedParsed then Left $ - let minimized = minimize unformattedParsed' (\e -> parse (layout width e) == Right (Whole e [])) + let minimized = minimize unformattedParsed' (\e -> parse (layout e) == Right (Whole e [])) in pleaseReport "Parses differently after formatting." <> "\n\nBefore formatting:\n" <> show minimized <> "\n\nAfter formatting:\n" - <> show (fromRight (error "TODO") $ parse (layout width minimized)) + <> show (fromRight (error "TODO") $ parse (layout minimized)) else if formattedOnce /= formattedTwice then @@ -66,12 +69,12 @@ formatVerify width path unformatted = do let minimized = minimize unformattedParsed' - (\e -> layout width e == layout width (fromRight (error "TODO") $ parse $ layout width e)) + (\e -> layout e == layout (fromRight (error "TODO") $ parse $ layout e)) in pleaseReport "Nixfmt is not idempotent." <> "\n\nAfter one formatting:\n" - <> unpack (layout width minimized) + <> unpack (layout minimized) <> "\n\nAfter two:\n" - <> unpack (layout width (fromRight (error "TODO") $ parse $ layout width minimized)) + <> unpack (layout (fromRight (error "TODO") $ parse $ layout minimized)) else Right formattedOnce where parse = first errorBundlePretty . Megaparsec.parse Parser.file path diff --git a/src/Nixfmt/Lexer.hs b/src/Nixfmt/Lexer.hs index 760aa291..6d28c9d8 100644 --- a/src/Nixfmt/Lexer.hs +++ b/src/Nixfmt/Lexer.hs @@ -183,13 +183,20 @@ pushTrivia t = modify (<> t) lexeme :: Parser a -> Parser (Ann a) lexeme p = do lastLeading <- takeTrivia + SourcePos{Text.Megaparsec.sourceLine = line} <- getSourcePos token <- preLexeme p parsedTrivia <- trivia -- This is the position of the next lexeme after the currently parsed one SourcePos{sourceColumn = col} <- getSourcePos let (trailing, nextLeading) = convertTrivia parsedTrivia col pushTrivia nextLeading - return $ Ann lastLeading token trailing + return $ + Ann + { preTrivia = lastLeading, + value = token, + Nixfmt.Types.sourceLine = line, + trailComment = trailing + } -- | Tokens normally have only leading trivia and one trailing comment on the same -- line. A whole x also parses and stores final trivia after the x. A whole also diff --git a/src/Nixfmt/Predoc.hs b/src/Nixfmt/Predoc.hs index 2e91402f..292aab2a 100644 --- a/src/Nixfmt/Predoc.hs +++ b/src/Nixfmt/Predoc.hs @@ -45,6 +45,11 @@ import qualified Data.List.NonEmpty as NonEmpty import Data.Maybe (fromMaybe) import Data.Text as Text (Text, concat, length, replicate, strip) import GHC.Stack (HasCallStack) +import Nixfmt.Types ( + LanguageElement, + mapAllTokens, + removeLineInfo, + ) -- | Sequential Spacings are reduced to a single Spacing by taking the maximum. -- This means that e.g. a Space followed by an Emptyline results in just an @@ -342,8 +347,15 @@ mergeSpacings Hardspace (Newlines x) = Newlines x mergeSpacings _ (Newlines x) = Newlines (x + 1) mergeSpacings _ y = y -layout :: (Pretty a) => Int -> a -> Text -layout w = (<> "\n") . Text.strip . layoutGreedy w . fixup . pretty +layout :: (Pretty a, LanguageElement a) => Int -> Bool -> a -> Text +layout width strict = + (<> "\n") + . Text.strip + . layoutGreedy width + . fixup + . pretty + -- In strict mode, set the line number of all tokens to zero + . (if strict then mapAllTokens removeLineInfo else id) -- 1. Move and merge Spacings. -- 2. Convert Softlines to Grouped Lines and Hardspaces to Texts. diff --git a/src/Nixfmt/Pretty.hs b/src/Nixfmt/Pretty.hs index d9e79cf8..120ef92b 100644 --- a/src/Nixfmt/Pretty.hs +++ b/src/Nixfmt/Pretty.hs @@ -1,5 +1,6 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TupleSections #-} @@ -54,6 +55,7 @@ import Nixfmt.Types ( TrailingComment (..), Trivium (..), Whole (..), + ann, hasTrivia, mapFirstToken, mapFirstToken', @@ -67,7 +69,11 @@ toLineComment (TrailingComment c) = LineComment $ " " <> c -- If the token has some trailing comment after it, move that in front of the token moveTrailingCommentUp :: Ann a -> Ann a -moveTrailingCommentUp (Ann pre a (Just post)) = Ann (pre ++ [toLineComment post]) a Nothing +moveTrailingCommentUp a@Ann{preTrivia, trailComment = Just post} = + a + { preTrivia = preTrivia ++ [toLineComment post], + trailComment = Nothing + } moveTrailingCommentUp a = a instance Pretty TrailingComment where @@ -103,14 +109,14 @@ instance Pretty [Trivium] where pretty trivia = hardline <> hcat trivia instance (Pretty a) => Pretty (Ann a) where - pretty (Ann leading x trailing') = - pretty leading <> pretty x <> pretty trailing' + pretty Ann{preTrivia, value, trailComment} = + pretty preTrivia <> pretty value <> pretty trailComment instance Pretty SimpleSelector where pretty (IDSelector i) = pretty i pretty (InterpolSelector interpol) = pretty interpol - pretty (StringSelector (Ann leading s trailing')) = - pretty leading <> prettySimpleString s <> pretty trailing' + pretty (StringSelector Ann{preTrivia, value, trailComment}) = + pretty preTrivia <> prettySimpleString value <> pretty trailComment instance Pretty Selector where pretty (Selector dot sel) = @@ -121,24 +127,25 @@ instance Pretty Binder where pretty (Inherit inherit Nothing ids semicolon) = group $ pretty inherit - <> ( if null ids - then pretty semicolon - else line <> nest (sepBy (if length ids < 4 then line else hardline) ids <> line' <> pretty semicolon) - ) + <> sep + <> nest (sepBy sep ids <> nosep <> pretty semicolon) + where + -- Only allow a single line if it's already on a single line and has few enough elements + (sep, nosep) = if sourceLine inherit == sourceLine semicolon && length ids < 4 then (line, line') else (hardline, hardline) -- `inherit (foo) bar` statement pretty (Inherit inherit (Just source) ids semicolon) = group $ pretty inherit <> nest ( group' RegularG (line <> pretty source) - <> if null ids - then pretty semicolon - else - line - <> sepBy (if length ids < 4 then line else hardline) ids - <> line' - <> pretty semicolon + <> sep + <> sepBy sep ids + <> nosep + <> pretty semicolon ) + where + -- Only allow a single line if it's already on a single line and has few enough elements + (sep, nosep) = if sourceLine inherit == sourceLine semicolon && length ids < 4 then (line, line') else (hardline, hardline) -- `foo = bar` pretty (Assignment selectors assign expr semicolon) = group $ @@ -152,17 +159,25 @@ instance Pretty Binder where -- be even more eager at expanding, except for empty sets and inherit statements. prettySet :: Bool -> (Maybe Leaf, Leaf, Items Binder, Leaf) -> Doc -- Empty attribute set -prettySet _ (krec, Ann [] paropen Nothing, Items [], parclose@(Ann [] _ _)) = - pretty (fmap (,hardspace) krec) <> pretty paropen <> hardspace <> pretty parclose +prettySet _ (krec, paropen@(LoneAnn _), Items [], parclose@Ann{preTrivia = []}) = + pretty (fmap (,hardspace) krec) <> pretty paropen <> sep <> pretty parclose + where + -- If the braces are on different lines, keep them like that + sep = if sourceLine paropen /= sourceLine parclose then hardline else hardspace -- Singleton sets are allowed to fit onto one line, -- but apart from that always expand. -prettySet wide (krec, Ann pre paropen post, binders, parclose) = +prettySet wide (krec, paropen@Ann{trailComment = post}, binders, parclose) = pretty (fmap (,hardspace) krec) - <> pretty (Ann pre paropen Nothing) + <> pretty (paropen{trailComment = Nothing}) <> surroundWith sep (nest $ pretty post <> prettyItems binders) <> pretty parclose where - sep = if wide && not (null (unItems binders)) then hardline else line + sep = + if wide && not (null (unItems binders)) + -- If the braces are on different lines, keep them like that + || sourceLine paropen /= sourceLine parclose + then hardline + else line prettyTermWide :: Term -> Doc prettyTermWide (Set krec paropen items parclose) = prettySet True (krec, paropen, items, parclose) @@ -171,8 +186,8 @@ prettyTermWide t = prettyTerm t -- | Pretty print a term without wrapping it in a group. prettyTerm :: Term -> Doc prettyTerm (Token t) = pretty t -prettyTerm (SimpleString (Ann leading s trailing')) = pretty leading <> prettySimpleString s <> pretty trailing' -prettyTerm (IndentedString (Ann leading s trailing')) = pretty leading <> prettyIndentedString s <> pretty trailing' +prettyTerm (SimpleString Ann{preTrivia, value, trailComment}) = pretty preTrivia <> prettySimpleString value <> pretty trailComment +prettyTerm (IndentedString Ann{preTrivia, value, trailComment}) = pretty preTrivia <> prettyIndentedString value <> pretty trailComment prettyTerm (Path p) = pretty p prettyTerm (Selection term selectors rest) = pretty term @@ -190,21 +205,27 @@ prettyTerm (Selection term selectors rest) = _ -> line' -- Empty list -prettyTerm (List (Ann leading paropen Nothing) (Items []) (Ann [] parclose trailing')) = - pretty leading <> pretty paropen <> hardspace <> pretty parclose <> pretty trailing' +prettyTerm (List paropen@Ann{trailComment = Nothing} (Items []) parclose@Ann{preTrivia = []}) = + pretty paropen <> sep <> pretty parclose + where + -- If the brackets are on different lines, keep them like that + sep = if sourceLine paropen /= sourceLine parclose then hardline else hardspace -- General list -- Always expand if len > 1 -prettyTerm (List (Ann pre paropen post) items parclose) = - pretty (Ann pre paropen Nothing) - <> surroundWith line (nest $ pretty post <> prettyItems items) +prettyTerm (List paropen@Ann{trailComment = post} items parclose) = + pretty (paropen{trailComment = Nothing}) + <> surroundWith sur (nest $ pretty post <> prettyItems items) <> pretty parclose + where + -- If the brackets are on different lines, keep them like that + sur = if sourceLine paropen /= sourceLine parclose then hardline else line prettyTerm (Set krec paropen items parclose) = prettySet False (krec, paropen, items, parclose) -- Parentheses -prettyTerm (Parenthesized paropen expr (Ann closePre parclose closePost)) = +prettyTerm (Parenthesized paropen expr parclose@Ann{preTrivia = closePre}) = group $ pretty (moveTrailingCommentUp paropen) <> nest (inner <> pretty closePre) - <> pretty (Ann [] parclose closePost) + <> pretty (parclose{preTrivia = []}) where inner = case expr of @@ -244,18 +265,18 @@ instance Pretty ParamAttr where -- This assumes that all items already have a trailing comma from earlier pre-processing moveParamAttrComment :: ParamAttr -> ParamAttr -- Simple parameter -moveParamAttrComment (ParamAttr (Ann trivia name (Just comment')) Nothing (Just (Ann [] comma Nothing))) = - ParamAttr (Ann trivia name Nothing) Nothing (Just (Ann [] comma (Just comment'))) +moveParamAttrComment (ParamAttr name@Ann{trailComment = Just comment'} Nothing (Just comma@(LoneAnn _))) = + ParamAttr (name{trailComment = Nothing}) Nothing (Just (comma{trailComment = Just comment'})) -- Parameter with default value -moveParamAttrComment (ParamAttr name (Just (qmark, def)) (Just (Ann [] comma Nothing))) = - ParamAttr name (Just (qmark, def')) (Just (Ann [] comma comment')) +moveParamAttrComment (ParamAttr name (Just (qmark, def)) (Just comma@(LoneAnn _))) = + ParamAttr name (Just (qmark, def')) (Just (comma{trailComment = comment'})) where -- Extract comment at the end of the line (def', comment') = mapLastToken' ( \case - (Ann trivia t (Just comment'')) -> (Ann trivia t Nothing, Just comment'') - ann -> (ann, Nothing) + a@Ann{trailComment = Just comment''} -> (a{trailComment = Nothing}, Just comment'') + a -> (a, Nothing) ) def moveParamAttrComment x = x @@ -268,25 +289,25 @@ moveParamsComments -- , name1 -- # comment -- , name2 - ( (ParamAttr name maybeDefault (Just (Ann trivia comma Nothing))) - : (ParamAttr (Ann trivia' name' trailing') maybeDefault' maybeComma') + ( (ParamAttr name maybeDefault (Just comma@Ann{preTrivia = trivia, trailComment = Nothing})) + : (ParamAttr name'@Ann{preTrivia = trivia'} maybeDefault' maybeComma') : xs ) = - ParamAttr name maybeDefault (Just (Ann [] comma Nothing)) - : moveParamsComments (ParamAttr (Ann (trivia ++ trivia') name' trailing') maybeDefault' maybeComma' : xs) + ParamAttr name maybeDefault (Just (comma{preTrivia = []})) + : moveParamsComments (ParamAttr (name'{preTrivia = trivia ++ trivia'}) maybeDefault' maybeComma' : xs) -- This may seem like a nonsensical case, but keep in mind that blank lines also count as comments (trivia) moveParamsComments -- , name -- # comment -- ellipsis - [ ParamAttr name maybeDefault (Just (Ann trivia comma Nothing)), - ParamEllipsis (Ann trivia' name' trailing') + [ ParamAttr name maybeDefault (Just comma@Ann{preTrivia = trivia, trailComment = Nothing}), + ParamEllipsis ellipsis@Ann{preTrivia = trivia'} ] = - [ ParamAttr name maybeDefault (Just (Ann [] comma Nothing)), - ParamEllipsis (Ann (trivia ++ trivia') name' trailing') + [ ParamAttr name maybeDefault (Just (comma{preTrivia = []})), + ParamEllipsis (ellipsis{preTrivia = trivia ++ trivia'}) ] -- Inject a trailing comma on the last element if nessecary -moveParamsComments [ParamAttr name def Nothing] = [ParamAttr name def (Just (Ann [] TComma Nothing))] +moveParamsComments [ParamAttr name@Ann{sourceLine} def Nothing] = [ParamAttr name def (Just (ann sourceLine TComma))] moveParamsComments (x : xs) = x : moveParamsComments xs moveParamsComments [] = [] @@ -295,7 +316,10 @@ instance Pretty Parameter where pretty (IDParameter i) = pretty i -- {}: pretty (SetParameter bopen [] bclose) = - group $ pretty (moveTrailingCommentUp bopen) <> hardspace <> pretty bclose + group $ pretty (moveTrailingCommentUp bopen) <> sep <> pretty bclose + where + -- If the braces are on different lines, keep them like that + sep = if sourceLine bopen /= sourceLine bclose then hardline else hardspace -- { stuff }: pretty (SetParameter bopen attrs bclose) = group $ @@ -308,18 +332,22 @@ instance Pretty Parameter where handleTrailingComma :: [ParamAttr] -> [Doc] handleTrailingComma [] = [] -- That's the case we're interested in - handleTrailingComma [ParamAttr name maybeDefault (Just (Ann [] TComma Nothing))] = + handleTrailingComma [ParamAttr name maybeDefault (Just (LoneAnn TComma))] = [pretty (ParamAttr name maybeDefault Nothing) <> trailing ","] handleTrailingComma (x : xs) = pretty x : handleTrailingComma xs - sep = case attrs of - [ParamEllipsis _] -> line - -- Attributes must be without default - [ParamAttr _ Nothing _] -> line - [ParamAttr _ Nothing _, ParamEllipsis _] -> line - [ParamAttr _ Nothing _, ParamAttr _ Nothing _] -> line - [ParamAttr _ Nothing _, ParamAttr _ Nothing _, ParamEllipsis _] -> line - _ -> hardline + sep = + -- If the braces are on different lines, keep them like that + if sourceLine bopen /= sourceLine bclose + then hardline + else case attrs of + [ParamEllipsis _] -> line + -- Attributes must be without default + [ParamAttr _ Nothing _] -> line + [ParamAttr _ Nothing _, ParamEllipsis _] -> line + [ParamAttr _ Nothing _, ParamAttr _ Nothing _] -> line + [ParamAttr _ Nothing _, ParamAttr _ Nothing _, ParamEllipsis _] -> line + _ -> hardline pretty (ContextParameter param1 at param2) = pretty param1 <> pretty at <> pretty param2 @@ -378,7 +406,7 @@ prettyApp indentFunction pre hasPost f a = ( Term ( Parenthesized open - (Application (Term (Token ident@(Ann _ fn@(Identifier _) _))) (Term body)) + (Application (Term (Token ident@Ann{value = fn@(Identifier _)})) (Term body)) close ) ) @@ -397,7 +425,7 @@ prettyApp indentFunction pre hasPost f a = -- Extract comment before the first function and move it out, to prevent functions being force-expanded (fWithoutComment, comment') = mapFirstToken' - ((\(Ann leading token trailing') -> (Ann [] token trailing', leading)) . moveTrailingCommentUp) + ((\a'@Ann{preTrivia} -> (a'{preTrivia = []}, preTrivia)) . moveTrailingCommentUp) f renderedF = pre <> group' Transparent (absorbApp fWithoutComment) @@ -446,22 +474,22 @@ isAbsorbableExpr expr = case expr of isAbsorbable :: Term -> Bool -- Multi-line indented string -isAbsorbable (IndentedString (Ann _ (_ : _ : _) _)) = True +isAbsorbable (IndentedString Ann{value = _ : _ : _}) = True isAbsorbable (Path _) = True -- Non-empty sets and lists isAbsorbable (Set _ _ (Items (_ : _)) _) = True isAbsorbable (List _ (Items (_ : _)) _) = True -isAbsorbable (Parenthesized (Ann [] _ Nothing) (Term t) _) = isAbsorbable t +isAbsorbable (Parenthesized (LoneAnn _) (Term t) _) = isAbsorbable t isAbsorbable _ = False isAbsorbableTerm :: Term -> Bool isAbsorbableTerm = isAbsorbable absorbParen :: Ann Token -> Expression -> Ann Token -> Doc -absorbParen (Ann pre' open post') expr (Ann pre'' close post'') = +absorbParen open@Ann{trailComment = post'} expr close@Ann{preTrivia = pre''} = group' Priority $ nest $ - pretty (Ann pre' open Nothing) + pretty (open{trailComment = Nothing}) -- Move any trailing comments on the opening parenthesis down into the body <> surroundWith line' @@ -469,13 +497,13 @@ absorbParen (Ann pre' open post') expr (Ann pre'' close post'') = nest $ pretty ( mapFirstToken - (\(Ann leading token trailing') -> Ann (maybeToList (toLineComment <$> post') ++ leading) token trailing') + (\a@Ann{preTrivia} -> a{preTrivia = maybeToList (toLineComment <$> post') ++ preTrivia}) expr ) -- Move any leading comments on the closing parenthesis up into the nest <> pretty pre'' ) - <> pretty (Ann [] close post'') + <> pretty (close{preTrivia = []}) -- Note that unlike for absorbable terms which can be force-absorbed, some expressions -- may turn out to not be absorbable. In that case, they should start with a line' so that @@ -509,15 +537,15 @@ absorbRHS expr = case expr of (With{}) -> group' RegularG $ line <> pretty expr -- Special case `//` and `++` operations to be more compact in some cases -- Case 1: two arguments, LHS is absorbable term, RHS fits onto the last line - (Operation (Term t) (Ann [] op Nothing) b) + (Operation (Term t) (LoneAnn op) b) | isAbsorbable t && isUpdateOrConcat op -> group' RegularG $ line <> group' Priority (prettyTermWide t) <> line <> pretty op <> hardspace <> pretty b -- Case 2a: LHS fits onto first line, RHS is an absorbable term - (Operation l (Ann [] op Nothing) (Term t)) + (Operation l (LoneAnn op) (Term t)) | isAbsorbable t && isUpdateOrConcat op -> group' RegularG $ line <> pretty l <> line <> group' Transparent (pretty op <> hardspace <> group' Priority (prettyTermWide t)) -- Case 2b: LHS fits onto first line, RHS is a function application - (Operation l (Ann [] op Nothing) (Application f a)) + (Operation l (LoneAnn op) (Application f a)) | isUpdateOrConcat op -> line <> group l <> line <> prettyApp False (pretty op <> hardspace) False f a -- Everything else: @@ -536,7 +564,7 @@ instance Pretty Expression where -- Let bindings are always fully expanded (no single-line form) -- We also take the comments around the `in` (trailing, leading and detached binder comments) -- and move them down to the first token of the body - pretty (Let let_ binders (Ann leading in_ trailing') expr) = + pretty (Let let_ binders Ann{preTrivia, value = in_, trailComment} expr) = letPart <> hardline <> inPart where -- Convert the TrailingComment to a Trivium, if present @@ -564,10 +592,10 @@ instance Pretty Expression where letBody = nest $ prettyItems (Items bindersWithoutComments) inPart = group $ - pretty (Ann [] in_ Nothing) + pretty in_ <> hardline -- Take our trailing and inject it between `in` and body - <> pretty (concat binderComments ++ leading ++ convertTrailing trailing') + <> pretty (concat binderComments ++ preTrivia ++ convertTrailing trailComment) <> pretty expr pretty (Assert assert cond semicolon expr) = group $ @@ -623,7 +651,7 @@ instance Pretty Expression where pretty (Application f a) = prettyApp False mempty False f a -- not chainable binary operators: <, >, <=, >=, ==, != - pretty (Operation a op@(Ann _ op' _) b) + pretty (Operation a op@Ann{value = op'} b) | op' == TLess || op' == TGreater || op' == TLessEqual || op' == TGreaterEqual || op' == TEqual || op' == TUnequal = pretty a <> softline <> pretty op <> hardspace <> pretty b -- all other operators @@ -675,13 +703,13 @@ isSimpleSelector (Selector _ (IDSelector _)) = True isSimpleSelector _ = False isSimple :: Expression -> Bool -isSimple (Term (SimpleString (Ann [] _ Nothing))) = True -isSimple (Term (IndentedString (Ann [] _ Nothing))) = True -isSimple (Term (Path (Ann [] _ Nothing))) = True -isSimple (Term (Token (Ann [] (Identifier _) Nothing))) = True +isSimple (Term (SimpleString (LoneAnn _))) = True +isSimple (Term (IndentedString (LoneAnn _))) = True +isSimple (Term (Path (LoneAnn _))) = True +isSimple (Term (Token (LoneAnn (Identifier _)))) = True isSimple (Term (Selection t selectors def)) = isSimple (Term t) && all isSimpleSelector selectors && isNothing def -isSimple (Term (Parenthesized (Ann [] _ Nothing) e (Ann [] _ Nothing))) = isSimple e +isSimple (Term (Parenthesized (LoneAnn _) e (LoneAnn _))) = isSimple e -- Function applications of simple terms are simple up to two arguments isSimple (Application (Application (Application _ _) _) _) = False isSimple (Application f a) = isSimple f && isSimple a diff --git a/src/Nixfmt/Types.hs b/src/Nixfmt/Types.hs index 3429bd71..03efa90a 100644 --- a/src/Nixfmt/Types.hs +++ b/src/Nixfmt/Types.hs @@ -1,10 +1,48 @@ {-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE RankNTypes #-} -module Nixfmt.Types where +module Nixfmt.Types ( + ParseErrorBundle, + Trivia, + Ann (.., LoneAnn), + ann, + Binder (..), + Expression (..), + File, + Fixity (..), + Item (..), + Items (..), + Leaf, + Operator (..), + ParamAttr (..), + Parameter (..), + Parser, + Path, + Selector (..), + SimpleSelector (..), + StringPart (..), + Term (..), + Token (..), + Whole (..), + TrailingComment (..), + Trivium (..), + removeLineInfo, + hasTrivia, + LanguageElement, + mapFirstToken, + mapFirstToken', + mapLastToken', + mapAllTokens, + operators, + tokenText, + walkSubprograms, +) where import Control.Monad.State (StateT) import Data.Bifunctor (first) @@ -14,7 +52,8 @@ import Data.List.NonEmpty as NonEmpty import Data.Maybe (maybeToList) import Data.Text (Text, pack) import Data.Void (Void) -import qualified Text.Megaparsec as MP (ParseErrorBundle, Parsec) +import Text.Megaparsec (Pos) +import qualified Text.Megaparsec as MP (ParseErrorBundle, Parsec, pos1) import Prelude hiding (String) -- | A @megaparsec@ @ParsecT@ specified for use with @nixfmt@. @@ -37,21 +76,40 @@ type Trivia = [Trivium] newtype TrailingComment = TrailingComment Text deriving (Eq, Show) -data Ann a - = Ann Trivia a (Maybe TrailingComment) +data Ann a = Ann + { preTrivia :: Trivia, + -- | The line of this value in the source code + sourceLine :: Pos, + value :: a, + trailComment :: Maybe TrailingComment + } deriving (Show) +removeLineInfo :: Ann a -> Ann a +removeLineInfo a = a{sourceLine = MP.pos1} + +-- | An annotated value without any trivia or trailing comment +pattern LoneAnn :: a -> Ann a +pattern LoneAnn a <- Ann [] _ a Nothing + hasTrivia :: Ann a -> Bool -hasTrivia (Ann [] _ Nothing) = False +hasTrivia (LoneAnn _) = False hasTrivia _ = True -ann :: a -> Ann a -ann a = Ann [] a Nothing +-- | Create a new annotated value without any annotations +ann :: Pos -> a -> Ann a +ann l v = + Ann + { preTrivia = [], + sourceLine = l, + value = v, + trailComment = Nothing + } -- | Equality of annotated syntax is defined as equality of their corresponding -- semantics, thus ignoring the annotations. instance (Eq a) => Eq (Ann a) where - Ann _ x _ == Ann _ y _ = x == y + Ann{value = x} == Ann{value = y} = x == y -- Trivia is ignored for Eq, so also don't show -- instance Show a => Show (Ann a) where @@ -62,9 +120,9 @@ data Item a Item a | -- | Trivia interleaved in items Comments Trivia - deriving (Foldable, Show) + deriving (Foldable, Show, Functor) -newtype Items a = Items {unItems :: [Item a]} +newtype Items a = Items {unItems :: [Item a]} deriving (Functor) instance (Eq a) => Eq (Items a) where (==) = (==) `on` concatMap Data.Foldable.toList . unItems @@ -184,15 +242,12 @@ class LanguageElement a where -- returned. This is useful for getting/extracting values mapFirstToken' :: (forall b. Ann b -> (Ann b, c)) -> a -> (a, c) - -- Map the last token of that expression, no matter how deep it sits - -- in the AST. This is useful for modifying comments - mapLastToken :: (forall b. Ann b -> Ann b) -> a -> a - mapLastToken f a = fst (mapLastToken' (\x -> (f x, ())) a) - -- Same as mapLastToken, but the mapping function also yields a value that may be -- returned. This is useful for getting/extracting values mapLastToken' :: (forall b. Ann b -> (Ann b, c)) -> a -> (a, c) + mapAllTokens :: (forall b. Ann b -> Ann b) -> a -> a + -- Walk all syntactically valid sub-expressions in a breadth-first search way. This allows -- minimizing failing test cases walkSubprograms :: a -> [Expression] @@ -201,6 +256,7 @@ instance LanguageElement (Ann a) where mapFirstToken' f = f mapLastToken' f = f walkSubprograms = error "unreachable" + mapAllTokens f = f instance LanguageElement SimpleSelector where mapFirstToken' f = \case @@ -212,9 +268,14 @@ instance LanguageElement SimpleSelector where walkSubprograms = \case (IDSelector name) -> [Term (Token name)] - (InterpolSelector (Ann _ str _)) -> pure $ Term $ SimpleString $ Ann [] [[str]] Nothing + (InterpolSelector Ann{sourceLine, value = str}) -> pure $ Term $ SimpleString $ ann sourceLine [[str]] (StringSelector str) -> [Term (SimpleString str)] + mapAllTokens f = \case + (IDSelector name) -> IDSelector $ f name + (InterpolSelector name) -> InterpolSelector $ f name + (StringSelector name) -> StringSelector $ f name + instance LanguageElement Selector where mapFirstToken' f (Selector Nothing ident) = first (Selector Nothing) $ mapFirstToken' f ident mapFirstToken' f (Selector (Just dot) ident) = first (\dot' -> Selector (Just dot') ident) $ mapFirstToken' f dot @@ -223,6 +284,17 @@ instance LanguageElement Selector where walkSubprograms (Selector _ ident) = walkSubprograms ident + mapAllTokens f (Selector dot ident) = Selector (f <$> dot) (mapAllTokens f ident) + +instance LanguageElement Binder where + mapFirstToken' _ _ = error "unused" + mapLastToken' _ _ = error "unused" + walkSubprograms _ = error "unused" + + mapAllTokens f = \case + (Inherit inherit from sels semicolon) -> Inherit (f inherit) (mapAllTokens f <$> from) (Prelude.map (mapAllTokens f) sels) (f semicolon) + (Assignment sels eq rhs semicolon) -> Assignment (Prelude.map (mapAllTokens f) sels) (f eq) (mapAllTokens f rhs) (f semicolon) + instance LanguageElement ParamAttr where mapFirstToken' _ _ = error "unreachable" mapLastToken' _ _ = error "unreachable" @@ -232,6 +304,11 @@ instance LanguageElement ParamAttr where (ParamAttr name (Just (_, def)) _) -> [Term (Token name), def] (ParamEllipsis _) -> [] + mapAllTokens f = \case + (ParamAttr name Nothing comma) -> ParamAttr (mapAllTokens f name) Nothing (f <$> comma) + (ParamAttr name (Just (qmark, def)) comma) -> ParamAttr (mapAllTokens f name) (Just (f qmark, mapAllTokens f def)) (f <$> comma) + (ParamEllipsis dots) -> ParamEllipsis $ f dots + instance LanguageElement Parameter where mapFirstToken' f = \case (IDParameter name) -> first IDParameter (f name) @@ -248,6 +325,11 @@ instance LanguageElement Parameter where (SetParameter _ bindings _) -> bindings >>= walkSubprograms (ContextParameter left _ right) -> walkSubprograms left ++ walkSubprograms right + mapAllTokens f = \case + (IDParameter name) -> IDParameter (f name) + (SetParameter open items close) -> SetParameter (f open) (Prelude.map (mapAllTokens f) items) (f close) + (ContextParameter first' at second) -> ContextParameter (mapAllTokens f first') (f at) (mapAllTokens f second) + instance LanguageElement Term where mapFirstToken' f = \case (Token leaf) -> first Token (f leaf) @@ -279,31 +361,44 @@ instance LanguageElement Term where (List _ items _) | Prelude.length (unItems items) == 1 -> case Prelude.head (unItems items) of (Item item) -> [Term item] (Comments _) -> [] - (List _ items _) -> + (List open items close) -> unItems items >>= \case Item item -> - [Term (List (ann TBrackOpen) (Items [Item item]) (ann TBrackClose))] + [Term (List (stripTrivia open) (Items [Item item]) (stripTrivia close))] Comments c -> - [Term (List (ann TBrackOpen) (Items [Comments c]) (ann TBrackClose))] + [Term (List (stripTrivia open) (Items [Comments c]) (stripTrivia close))] (Set _ _ items _) | Prelude.length (unItems items) == 1 -> case Prelude.head (unItems items) of (Item (Inherit _ from sels _)) -> (Term <$> maybeToList from) ++ concatMap walkSubprograms sels (Item (Assignment sels _ expr _)) -> expr : concatMap walkSubprograms sels (Comments _) -> [] - (Set _ _ items _) -> + (Set _ open items close) -> unItems items >>= \case -- Map each binding to a singleton set (Item item) -> - [Term (Set Nothing (ann TBraceOpen) (Items [Item item]) (ann TBraceClose))] - (Comments c) -> [emptySet c] + [Term (Set Nothing (stripTrivia open) (Items [Item item]) (stripTrivia close))] + (Comments c) -> + [Term (Set Nothing (stripTrivia open) (Items [Comments c]) (stripTrivia close))] (Selection term sels Nothing) -> Term term : (sels >>= walkSubprograms) (Selection term sels (Just (_, def))) -> Term term : (sels >>= walkSubprograms) ++ [Term def] (Parenthesized _ expr _) -> [expr] -- The others are already minimal _ -> [] where - emptySet c = Term (Set Nothing (ann TBraceOpen) (Items [Comments c]) (ann TBraceClose)) + -- TODO: Don't do this stripping at all, Doesn't seem very critical + stripTrivia a = a{preTrivia = [], trailComment = Nothing} + + mapAllTokens f = \case + (Token leaf) -> Token (f leaf) + (SimpleString string) -> SimpleString (f string) + (IndentedString string) -> IndentedString (f string) + (Path path) -> Path (f path) + (List open items close) -> List (f open) (mapAllTokens f <$> items) (f close) + (Set rec open items close) -> Set (f <$> rec) (f open) (mapAllTokens f <$> items) (f close) + (Selection term sels (Just (orToken, def))) -> Selection (mapAllTokens f term) (Prelude.map (mapAllTokens f) sels) $ Just (f orToken, mapAllTokens f def) + (Selection term sels Nothing) -> Selection (mapAllTokens f term) (Prelude.map (mapAllTokens f) sels) Nothing + (Parenthesized open expr close) -> Parenthesized (f open) (mapAllTokens f expr) (f close) instance LanguageElement Expression where mapFirstToken' f = \case @@ -336,11 +431,11 @@ instance LanguageElement Expression where walkSubprograms = \case (Term term) -> walkSubprograms term (With _ expr0 _ expr1) -> [expr0, expr1] - (Let _ items _ body) -> + (Let Ann{sourceLine = startLine} items Ann{sourceLine = endLine} body) -> body : ( unItems items >>= \case -- Map each binding to a singleton set - (Item item) -> [Term (Set Nothing (ann TBraceOpen) (Items [Item item]) (ann TBraceClose))] + (Item item) -> [Term (Set Nothing (ann startLine TBraceOpen) (Items [Item item]) (ann endLine TBraceClose))] (Comments _) -> [] ) (Assert _ cond _ body) -> [cond, body] @@ -350,13 +445,26 @@ instance LanguageElement Expression where (Abstraction param _ (Term (Token _))) -> walkSubprograms param -- Otherwise, to separate the parameter from the body while keeping it a valid expression, -- replace the body with just a token. Return the body (a valid expression on its own) separately - (Abstraction param colon body) -> [Abstraction param colon (Term (Token (ann (Identifier "_")))), body] + (Abstraction param colon@Ann{sourceLine} body) -> [Abstraction param colon (Term (Token (ann sourceLine (Identifier "_")))), body] (Application g a) -> [g, a] (Operation left _ right) -> [left, right] (MemberCheck name _ sels) -> name : (sels >>= walkSubprograms) (Negation _ expr) -> [expr] (Inversion _ expr) -> [expr] + mapAllTokens f = \case + (Term term) -> Term (mapAllTokens f term) + (With with expr0 semicolon expr1) -> With (f with) (mapAllTokens f expr0) (f semicolon) (mapAllTokens f expr1) + (Let let_ items in_ body) -> Let (f let_) (mapAllTokens f <$> items) (f in_) (mapAllTokens f body) + (Assert assert cond semicolon body) -> Assert (f assert) (mapAllTokens f cond) (f semicolon) (mapAllTokens f body) + (If if_ expr0 then_ expr1 else_ expr2) -> If (f if_) (mapAllTokens f expr0) (f then_) (mapAllTokens f expr1) (f else_) (mapAllTokens f expr2) + (Abstraction param colon body) -> Abstraction (mapAllTokens f param) (f colon) (mapAllTokens f body) + (Application g a) -> Application (mapAllTokens f g) (mapAllTokens f a) + (Operation left op right) -> Operation (mapAllTokens f left) (f op) (mapAllTokens f right) + (MemberCheck name dot sels) -> MemberCheck (mapAllTokens f name) (f dot) (Prelude.map (mapAllTokens f) sels) + (Negation not_ expr) -> Negation (f not_) (mapAllTokens f expr) + (Inversion tilde expr) -> Inversion (f tilde) (mapAllTokens f expr) + instance LanguageElement (Whole Expression) where mapFirstToken' f (Whole a trivia) = first (`Whole` trivia) (mapFirstToken' f a) @@ -366,6 +474,8 @@ instance LanguageElement (Whole Expression) where walkSubprograms (Whole a _) = [a] + mapAllTokens f (Whole a trivia) = Whole (mapAllTokens f a) trivia + instance (LanguageElement a) => LanguageElement (NonEmpty a) where mapFirstToken' f (x :| _) = first pure $ mapFirstToken' f x @@ -374,6 +484,8 @@ instance (LanguageElement a) => LanguageElement (NonEmpty a) where walkSubprograms = error "unreachable" + mapAllTokens f = NonEmpty.map (mapAllTokens f) + data Token = Integer Int | Float Double diff --git a/test/diff/apply/out-pure.nix b/test/diff/apply/out-pure.nix new file mode 100644 index 00000000..42497b7f --- /dev/null +++ b/test/diff/apply/out-pure.nix @@ -0,0 +1,352 @@ +[ + ( + # Function call with comment + mapAttrsToStringsSep "\n" mkSection attrsOfAttrs + ) + # Function call with comment + (mapAttrsToStringsSep "\n" mkSection attrsOfAttrs) + ( + # Function call with comment + mapAttrsToStringsSep "\n" mkSection attrsOfAttrs + ) + + # Same song again, but within function application + + (foo bar baz ( + # Function call with comment + mapAttrsToStringsSep "\n" mkSection attrsOfAttrs + )) + (foo bar baz + # Function call with comment + (mapAttrsToStringsSep "\n" mkSection attrsOfAttrs) + ) + (foo bar baz ( + # Function call with comment + mapAttrsToStringsSep "\n" mkSection attrsOfAttrs + )) + + # And again, but with wide function application + + (foo + [ + 1 + 2 # multiline + ] + baz + ( + # Function call with comment + mapAttrsToStringsSep "\n" mkSection attrsOfAttrs + ) + ) + (foo + [ + 1 + 2 # multiline + ] + bar + baz + # Function call with comment + (mapAttrsToStringsSep "\n" mkSection attrsOfAttrs) + ) + (foo + [ + 1 + 2 # multiline + ] + bar + baz + ( + # Function call with comment + mapAttrsToStringsSep "\n" mkSection attrsOfAttrs + ) + ) + + # Now in attribute set position + { + a = + # Function call with comment + mapAttrsToStringsSep "\n" mkSection attrsOfAttrs; + b = # Function call with comment + mapAttrsToStringsSep "\n" mkSection attrsOfAttrs; + } + [ + (mapAttrsToStringsSep [ + force + long + ] "\n" mkSection attrsOfAttrs) + ] + (a b) + ((a b) (a b) + ( + # b + a c + ) + ( + # a + # c + b d # e + ) + ) + '' + otherModules=${ + pkgs.writeText "other-modules.json" ( + l.toJSON ( + l.mapAttrs ( + pname: subOutputs: + let + pkg = subOutputs.packages."${pname}".overrideAttrs (old: { + buildScript = "true"; + installMethod = "copy"; + }); + in + "${pkg}/lib/node_modules/${pname}/node_modules" + ) outputs.subPackages + ) + ) + } + '' + { + name1 = function arg { asdf = 1; }; + + name2 = function arg { asdf = 1; } argument; + + name3 = function arg { asdf = 1; } { qwer = 12345; } argument; + } + { + name1 = function arg { asdf = 1; }; + + name2 = function arg { + asdf = 1; + # multiline + } argument; + + name3 = function arg { + asdf = 1; + # multiline + } { qwer = 12345; } argument; + } + { + name4 = function arg { asdf = 1; } { + qwer = 12345; + qwer2 = 54321; + } argument; + } + { + option1 = function arg { asdf = 1; } { + qwer = 12345; + qwer2 = 54321; + } lastArg; + + option2 = function arg { asdf = 1; } { + qwer = 12345; + qwer2 = 54321; + } lastArg; + + option3 = function arg { asdf = 1; } { + qwer = 12345; + qwer2 = 54321; + } lastArg; + } + # https://github.com/kamadorueda/alejandra/issues/372#issuecomment-1435083516 + { + outputs = + { utils }: + # For each supported platform, + utils.lib.eachDefaultSystem (system: { }); + } + { + escapeSingleline = libStr.escape [ + "\\" + ''"'' + "\${" + ]; + escapeMultiline = + libStr.replaceStrings + [ + "\${" + "''" + ] + [ + "''\${" + "'''" + ]; + test = + foo + [ + # multiline + 1 + 2 + 3 + ] + [ ] + { } + [ ] + [ + 1 + 2 + 3 # multiline + ]; + looooooooong = ( + toINI { + inherit + mkSectionName + mkKeyValue + listsAsDuplicateKeys + aaaaaaaa + ; + } sections + ); + looooooooong' = toINI { + inherit + mkSectionName + mkKeyValue + listsAsDuplicateKeys + aaaaaaaa + ; + } sections; + } + + # Test breakup behavior at different line lengths + { + name = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name_ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name__ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name___ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name____ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name_____ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name______ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name_______ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name________ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name_________ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name__________ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name___________ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name____________ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name_____________ = sanitizeDerivationName (builtins.substring 33 (-1) (path')); + name______________ = sanitizeDerivationName ( + builtins.substring 33 (-1) (path') + ); + name_______________ = sanitizeDerivationName ( + builtins.substring 33 (-1) (path') + ); + name________________ = sanitizeDerivationName ( + builtins.substring 33 (-1) (path') + ); + name_________________ = sanitizeDerivationName ( + builtins.substring 33 (-1) (path') + ); + name__________________ = sanitizeDerivationName ( + builtins.substring 33 (-1) (path') + ); + } + # Same but without binders + [ + (sanitizeDerivationName (builtins.substring 33 (-1) (baseNameOf path'))) + (sanitizeDerivationName_ (builtins.substring 33 (-1) (baseNameOf path'))) + (sanitizeDerivationName__ (builtins.substring 33 (-1) (baseNameOf path'))) + (sanitizeDerivationName___ (builtins.substring 33 (-1) (baseNameOf path'))) + (sanitizeDerivationName____ (builtins.substring 33 (-1) (baseNameOf path'))) + (sanitizeDerivationName_____ (builtins.substring 33 (-1) (baseNameOf path'))) + (sanitizeDerivationName______ (builtins.substring 33 (-1) (baseNameOf path'))) + (sanitizeDerivationName_______ (builtins.substring 33 (-1) (baseNameOf path'))) + (sanitizeDerivationName________ (builtins.substring 33 (-1) (baseNameOf path'))) + (sanitizeDerivationName_________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + (sanitizeDerivationName__________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + (sanitizeDerivationName___________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + (sanitizeDerivationName____________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + (sanitizeDerivationName_____________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + (sanitizeDerivationName______________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + (sanitizeDerivationName_______________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + (sanitizeDerivationName________________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + (sanitizeDerivationName_________________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + (sanitizeDerivationName__________________ ( + builtins.substring 33 (-1) (baseNameOf path') + )) + ] + # Function calls with lambdas as last argument + { + overrideArgs = copyArgs (newArgs: makeOverridable f (overrideWith newArgs)); + overrideArgs_ = copyArgs (newArgs: makeOverridable f (overrideWith newArgs)); + overrideArgs__ = copyArgs (newArgs: makeOverridable f (overrideWith newArgs)); + overrideArgs___ = copyArgs (newArgs: makeOverridable f (overrideWith newArgs)); + overrideArgs____ = copyArgs (newArgs: makeOverridable f (overrideWith newArgs)); + # Get a list of suggested argument names for a given missing one + getSuggestions = + arg: + lib.pipe (autoArgs // args) [ + lib.attrNames + # Only use ones that are at most 2 edits away. While mork would work, + # levenshteinAtMost is only fast for 2 or less. + (lib.filter (lib.strings.levenshteinAtMost 2 arg)) + # Put strings with shorter distance first + (lib.sort (x: y: lib.strings.levenshtein x arg < lib.strings.levenshtein y arg)) + # Only take the first couple results + (lib.take 3) + # Quote all entries + (map (x: ''"'' + x + ''"'')) + ]; + } + # Function calls with multiline functions + { + foo = + (callPackage ../generic-builders/manifest.nix { + # A lot of values here + }).overrideAttrs + (prevAttrs: { + # stuff here + }); + # Variant with a selection on the function without parentheses + foo2 = + { + # A lot of values here + } + .overrideAttrs + (prevAttrs: { + # stuff here + }); + # Also test within parenthesized function instead of just attribute sets + foo3 = ( + (callPackage ../generic-builders/manifest.nix { + # A lot of values here + }).overrideAttrs + stuff + (prevAttrs: { + # stuff here + }) + ); + # Add a comment at a bad place + foo4 = ( + # comment + (callPackage ../generic-builders/manifest.nix { + # A lot of values here + }).overrideAttrs + stuff + (prevAttrs: { + # stuff here + }) + ); + } + (function ( + something + # ... + ) { }) + + (badge "https://github.com/maralorn/haskell-taskwarrior/actions/workflows/haskell.yml/badge.svg" "https://github.com/maralorn/haskell-taskwarrior/actions") +] diff --git a/test/diff/apply/out.nix b/test/diff/apply/out.nix index 42497b7f..a30e59ad 100644 --- a/test/diff/apply/out.nix +++ b/test/diff/apply/out.nix @@ -113,17 +113,25 @@ name3 = function arg { asdf = 1; } { qwer = 12345; } argument; } { - name1 = function arg { asdf = 1; }; + name1 = function arg { + asdf = 1; + }; name2 = function arg { asdf = 1; # multiline } argument; - name3 = function arg { - asdf = 1; - # multiline - } { qwer = 12345; } argument; + name3 = + function arg + { + asdf = 1; + # multiline + } + { + qwer = 12345; + } + argument; } { name4 = function arg { asdf = 1; } { diff --git a/test/diff/assert/out-pure.nix b/test/diff/assert/out-pure.nix new file mode 100644 index 00000000..3760f374 --- /dev/null +++ b/test/diff/assert/out-pure.nix @@ -0,0 +1,100 @@ +[ + ( + assert b; + e + ) + ( + assert b; # d + e + ) + ( + assert b # c + ; + e + ) + ( + assert b # c + ; # d + e + ) + ( + # a + assert b; + e + ) + ( + # a + assert b; # d + e + ) + ( + # a + assert b # c + ; + e + ) + ( + # a + assert b # c + ; # d + e + ) + ( + assert b; + cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc + ) + ( + assert b; + cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc + ) + ( + assert + let + int = a: if a then 1 else 0; + xor = a: b: ((builtins.bitXor (int a) (int b)) == 1); + in + lib.assertMsg (xor (gitRelease != null) (officialRelease != null)) ( + "must specify `gitRelease` or `officialRelease`" + + (lib.optionalString (gitRelease != null) " — not both") + ); + assert if true then 1 else 0; + assert + if true then # multiline + 1 + else + 0; + assert + with lib.strings; + (versionAtLeast stdenv.cc.version "7.1" && versionOlder stdenv.cc.version "13"); + assert ( + stringLength (drvName (toString oldDependency)) + == stringLength (drvName (toString newDependency)) + ); + assert ( + lib.assertMsg (!enableGoldPlugin) + "Gold plugin cannot be enabled on LLVM16 due to a upstream issue: https://github.com/llvm/llvm-project/issues/61350" + ); + assert lib.assertMsg (!enableGoldPlugin) + "Gold plugin cannot be enabled on LLVM16 due to a upstream issue: https://github.com/llvm/llvm-project/issues/61350"; + assert ( + builtins.length eriAm == eriDeriv + 1 + && builtins.foldl' (a: b: a && b) true ( + builtins.map (a: a <= maxAm && a >= 0) eriAm + ) + ); + assert assertMsg (originalValid -> absConcatOrig == absConcatNormalised) + "For valid subpath \"${str}\", appending to an absolute Nix path value gives \"${absConcatOrig}\", but appending the normalised result \"${tryOnce.value}\" gives a different value \"${absConcatNormalised}\""; + assert lib.assertMsg (strw <= width) + "fixedWidthString: requested string length (${toString width}) must not be shorter than actual length (${toString strw})"; + assert lib.foldl ( + pass: { assertion, message }: if assertion final then pass else throw message + ) true (final.parsed.abi.assertions or [ ]); + assert + getErrors { + nixpkgs.localSystem = pkgs.stdenv.hostPlatform; + nixpkgs.hostPlatform = pkgs.stdenv.hostPlatform; + nixpkgs.pkgs = pkgs; + } == [ ]; + [ ] + ) +] diff --git a/test/diff/attr_set/in.nix b/test/diff/attr_set/in.nix index 07c182fe..e9ca7d84 100644 --- a/test/diff/attr_set/in.nix +++ b/test/diff/attr_set/in.nix @@ -5,6 +5,8 @@ {a=1; } + { + } { } diff --git a/test/diff/attr_set/out-pure.nix b/test/diff/attr_set/out-pure.nix new file mode 100644 index 00000000..f28d2e25 --- /dev/null +++ b/test/diff/attr_set/out-pure.nix @@ -0,0 +1,381 @@ +[ + { } + { + # a + } + { a = 1; } + { a = 1; } + + { } + { + + } + + { + a = { + + }; + } + + { b = 1; } + { + b = 1; # c + } + { + # a + b = 1; + } + { + # a + b = 1; # c + } + + rec { c = 1; } + rec { + c = 1; # d + } + rec { + # b + c = 1; + } + rec { + # b + c = 1; # d + } + rec # a + { + c = 1; + } + rec # a + { + c = 1; # d + } + rec # a + { + # b + c = 1; + } + rec # a + { + # b + c = 1; # d + } + + { + a = rec { + a = { + a = rec { + a = { + a = rec { + a = { + a = rec { + a = { + a = rec { + a = { }; + }; + }; + }; + }; + }; + }; + }; + }; + }; + } + + rec { + + c = 1; + + e = 1; + + } + + rec + # a + { + + # b + + c = 1; + + # d + + e = 1; + + # f + + } + { + x = + { + foo = 1; + bar = 2; + # multiline + } + .${x}; + y = # more multiline + { + foo = 1; + bar = 2; + # multiline + } + .${x}; + z = + functionCall + { + # multi + #line + } + [ + # several + items + ]; + a = + [ + some + flags # multiline + ] + ++ [ short ] + ++ [ + more + stuff # multiline + ] + ++ (if foo then [ bar ] else [ baz ]) + ++ [ ] + ++ (optionals condition [ + more + items + ]); + b = with pkgs; [ + a + lot + of + packages + ]; + } + { + systemd.initrdBi = lib.mkIf config.boot.initrd.services.lvm.enable [ pkgs.vdo ]; + systemd.initrdBin = lib.mkIf config.boot.initrd.services.lvm.enable [ + pkgs.vdo + ]; + systemd.initrdBin_ = lib.mkIf config.boot.initrd.services.lvm.enable [ + pkgs.vdo + ]; + systemd.initrdBin__ = lib.mkIf config.boot.initrd.services.lvm.enable [ + pkgs.vdo + ]; + systemd.initrdBin___ = lib.mkIf config.boot.initrd.services.lvm.enable [ + pkgs.vdo + ]; + } + { + patches = [ + (substituteAll { + src = ./extensionOverridesPatches/vitals_at_corecoding.com.patch; + gtop_path = "${libgtop}/lib/girepository-1.0"; + }) + ]; + } + { + programs.ssh.knownHosts = + lib.mapAttrs (host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + }) secret-config.ssh-hosts + // { + foo = "bar"; + }; + programs.ssh.knownHosts2 = + someStuff + // lib.mapAttrs (host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + }) secret-config.ssh-hosts + // { + foo = "bar"; + }; + programs.ssh.knownHosts3 = + lib.mapAttrs ( + host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + } + ) + // { + foo = "bar"; + }; + programs.ssh.knownHosts4 = + someStuff + // lib.mapAttrs ( + host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + } + ) + // { + foo = "bar"; + }; + programs.ssh.knownHosts5 = + someStuff + // lib.mapAttrs ( + host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + } + ); + programs.ssh.knownHosts6 = + someStuff + // lib.mapAttrs (host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + }) secret-config.ssh-hosts; + programs.ssh.knownHosts7 = + someStuff # multiline + // lib.mapAttrs ( + host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + } + ); + programs.ssh.knownHosts8 = + someStuff # multiline + // lib.mapAttrs (host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + }) secret-config.ssh-hosts; + programs.ssh.knownHosts9 = + { + multi = 1; + line = 2; + } + // lib.mapAttrs ( + host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + } + ); + programs.ssh.knownHosts10 = + { + multi = 1; + line = 2; + } + // lib.mapAttrs (host_name: publicKey: { + inherit publicKey; + extraHostNames = [ + "${host_name}.m-0.eu" + "${host_name}.vpn.m-0.eu" + "${host_name}.lo.m-0.eu" + ]; + }) secret-config.ssh-hosts; + } + + # Parentheses + { + a = ({ }); + b = ([ + 1 + 2 + 3 + ]); + c = (if null then true else false); + d = ( + let + in + [ + 1 + 2 + 3 + ] + ); + e = ( + if null then + true + else + [ + 1 + 2 + 3 + ] + ); + # FIXME: This one exposes a really weird bug in the underlying + # pretty printing engine. + # (It's probably the same one that causes weird indentation in + # functions with multiline function) + # f = /* comment */ (if null then true else [ 1 2 3 ]); + + a = (with a; { }); + b = ( + with a; + [ + 1 + 2 + 3 + ] + ); + c = (with a; if null then true else false); + d = ( + with a; + let + in + [ + 1 + 2 + 3 + ] + ); + } + + # Comments + { + fontsForXServer = + config.fonts.fonts + ++ + # We don't want these fonts in fonts.conf, because then modern, + # fontconfig-based applications will get horrible bitmapped + # Helvetica fonts. It's better to get a substitution (like Nimbus + # Sans) than that horror. But we do need the Adobe fonts for some + # old non-fontconfig applications. (Possibly this could be done + # better using a fontconfig rule.) + [ + pkgs.xorg.fontadobe100dpi + pkgs.xorg.fontadobe75dpi + ]; + } +] diff --git a/test/diff/attr_set/out.nix b/test/diff/attr_set/out.nix index 7e5ec04b..7b52a916 100644 --- a/test/diff/attr_set/out.nix +++ b/test/diff/attr_set/out.nix @@ -4,8 +4,12 @@ # a } { a = 1; } - { a = 1; } + { + a = 1; + } + { + } { } diff --git a/test/diff/comment/out-pure.nix b/test/diff/comment/out-pure.nix new file mode 100644 index 00000000..138f59c0 --- /dev/null +++ b/test/diff/comment/out-pure.nix @@ -0,0 +1,161 @@ +[ + + # @ + + /** + @ + * + */ + + /* + @ + @ + @ + */ + + /* + @ + @ + @ + */ + + /* + @ + @ + @ + */ + + /* + @ + @ + @ + */ + + /* + test + test + */ + + /* + test + test + */ + + # FOO + + /** + FOO + */ + + /* + FOO + BAR + */ + + /** + Concatenate a list of strings with a separator between each element + + # Example + + ```nix + concatStringsSep "/" ["usr" "local" "bin"] + => "usr/local/bin" + ``` + + # Type + + ``` + concatStringsSep :: string -> [string] -> string + ``` + */ + + /* + Concatenate a list of strings with a separator between each element + + # Example + + ```nix + concatStringsSep "/" ["usr" "local" "bin"] + => "usr/local/bin" + ``` + + # Type + + ``` + concatStringsSep :: string -> [string] -> string + ``` + */ + + /* + Concatenate a list of strings with a separator between each element + + # Example + + ```nix + concatStringsSep "/" ["usr" "local" "bin"] + => "usr/local/bin" + ``` + + # Type + + ``` + concatStringsSep :: string -> [string] -> string + ``` + */ + + [ + # 1 + #2 + a # 3 + b + c # 4 + #5 + + #6 + + d + #7 + ] + + { + a = 123; # comment + } + + { + # 1 + #2 + a = 1; # 3 + b = 1; + c = 1; # 4 + #5 + + #6 + + d = 1; + #7 + } + + ( + let # 1 + #2 + a = 1; # 3 + b = 1; + c = 1; # 4 + #5 + + #6 + + d = 1; + in + #7 + d + ) + + ( + { + a, # comment + b ? 2, # comment + }: + _ + ) +] diff --git a/test/diff/dynamic/out-pure.nix b/test/diff/dynamic/out-pure.nix new file mode 100644 index 00000000..af0cbff1 --- /dev/null +++ b/test/diff/dynamic/out-pure.nix @@ -0,0 +1,7 @@ +a.${ + # b + c.${ + # d + e.${f} + } # g +} diff --git a/test/diff/idioms/out-pure.nix b/test/diff/idioms/out-pure.nix new file mode 100644 index 00000000..e03bc506 --- /dev/null +++ b/test/diff/idioms/out-pure.nix @@ -0,0 +1,20 @@ +[ + { + meta = with lib; { + a = 1; + b = 2; + c = 3; + }; + } + + { + meta = + with lib; + # comment + { + a = 1; + b = 2; + c = 3; + }; + } +] diff --git a/test/diff/idioms_lib_1/out-pure.nix b/test/diff/idioms_lib_1/out-pure.nix new file mode 100644 index 00000000..3c4520d9 --- /dev/null +++ b/test/diff/idioms_lib_1/out-pure.nix @@ -0,0 +1,10 @@ +{ + traceIf = + # Predicate to check + pred: + # Message that should be traced + msg: + # Value to return + x: + if pred then trace msg x else x; +} diff --git a/test/diff/idioms_lib_2/out-pure.nix b/test/diff/idioms_lib_2/out-pure.nix new file mode 100644 index 00000000..1fc274f0 --- /dev/null +++ b/test/diff/idioms_lib_2/out-pure.nix @@ -0,0 +1,516 @@ +{ lib }: + +rec { + + ## Simple (higher order) functions + + /* + The identity function + For when you need a function that does “nothing”. + + Type: id :: a -> a + */ + id = + # The value to return + x: x; + + /* + The constant function + + Ignores the second argument. If called with only one argument, + constructs a function that always returns a static value. + + Type: const :: a -> b -> a + Example: + let f = const 5; in f 10 + => 5 + */ + const = + # Value to return + x: + # Value to ignore + y: + x; + + /* + Pipes a value through a list of functions, left to right. + + Type: pipe :: a -> [] -> + Example: + pipe 2 [ + (x: x + 2) # 2 + 2 = 4 + (x: x * 2) # 4 * 2 = 8 + ] + => 8 + + # ideal to do text transformations + pipe [ "a/b" "a/c" ] [ + + # create the cp command + (map (file: ''cp "${src}/${file}" $out\n'')) + + # concatenate all commands into one string + lib.concatStrings + + # make that string into a nix derivation + (pkgs.runCommand "copy-to-out" {}) + + ] + => + + The output type of each function has to be the input type + of the next function, and the last function returns the + final value. + */ + pipe = + val: functions: + let + reverseApply = x: f: f x; + in + builtins.foldl' reverseApply val functions; + + # note please don’t add a function like `compose = flip pipe`. + # This would confuse users, because the order of the functions + # in the list is not clear. With pipe, it’s obvious that it + # goes first-to-last. With `compose`, not so much. + + ## Named versions corresponding to some builtin operators. + + /* + Concatenate two lists + + Type: concat :: [a] -> [a] -> [a] + + Example: + concat [ 1 2 ] [ 3 4 ] + => [ 1 2 3 4 ] + */ + concat = x: y: x ++ y; + + # boolean “or” + or = x: y: x || y; + + # boolean “and” + and = x: y: x && y; + + # bitwise “and” + bitAnd = + builtins.bitAnd + or (import ./zip-int-bits.nix (a: b: if a == 1 && b == 1 then 1 else 0)); + + # bitwise “or” + bitOr = + builtins.bitOr + or (import ./zip-int-bits.nix (a: b: if a == 1 || b == 1 then 1 else 0)); + + # bitwise “xor” + bitXor = + builtins.bitXor or (import ./zip-int-bits.nix (a: b: if a != b then 1 else 0)); + + # bitwise “not” + bitNot = builtins.sub (-1); + + /* + Convert a boolean to a string. + + This function uses the strings "true" and "false" to represent + boolean values. Calling `toString` on a bool instead returns "1" + and "" (sic!). + + Type: boolToString :: bool -> string + */ + boolToString = b: if b then "true" else "false"; + + /* + Merge two attribute sets shallowly, right side trumps left + + mergeAttrs :: attrs -> attrs -> attrs + + Example: + mergeAttrs { a = 1; b = 2; } { b = 3; c = 4; } + => { a = 1; b = 3; c = 4; } + */ + mergeAttrs = + # Left attribute set + x: + # Right attribute set (higher precedence for equal keys) + y: + x // y; + + /* + Flip the order of the arguments of a binary function. + + Type: flip :: (a -> b -> c) -> (b -> a -> c) + + Example: + flip concat [1] [2] + => [ 2 1 ] + */ + flip = + f: a: b: + f b a; + + /* + Apply function if the supplied argument is non-null. + + Example: + mapNullable (x: x+1) null + => null + mapNullable (x: x+1) 22 + => 23 + */ + mapNullable = + # Function to call + f: + # Argument to check for null before passing it to `f` + a: + if a == null then a else f a; + + # Pull in some builtins not included elsewhere. + inherit (builtins) + pathExists + readFile + isBool + isInt + isFloat + add + sub + lessThan + seq + deepSeq + genericClosure + ; + + ## nixpkgs version strings + + # Returns the current full nixpkgs version number. + version = release + versionSuffix; + + # Returns the current nixpkgs release number as string. + release = lib.strings.fileContents ../.version; + + /* + Returns the current nixpkgs release code name. + + On each release the first letter is bumped and a new animal is chosen + starting with that new letter. + */ + codeName = "Quokka"; + + # Returns the current nixpkgs version suffix as string. + versionSuffix = + let + suffixFile = ../.version-suffix; + in + if pathExists suffixFile then + lib.strings.fileContents suffixFile + else + "pre-git"; + + /* + Attempts to return the the current revision of nixpkgs and + returns the supplied default value otherwise. + + Type: revisionWithDefault :: string -> string + */ + revisionWithDefault = + # Default value to return if revision can not be determined + default: + let + revisionFile = "${toString ./..}/.git-revision"; + gitRepo = "${toString ./..}/.git"; + in + if lib.pathIsGitRepo gitRepo then + lib.commitIdFromGitRepo gitRepo + else if lib.pathExists revisionFile then + lib.fileContents revisionFile + else + default; + + nixpkgsVersion = builtins.trace "`lib.nixpkgsVersion` is deprecated, use `lib.version` instead!" version; + + /* + Determine whether the function is being called from inside a Nix + shell. + + Type: inNixShell :: bool + */ + inNixShell = builtins.getEnv "IN_NIX_SHELL" != ""; + + ## Integer operations + + # Return minimum of two numbers. + min = x: y: if x < y then x else y; + + # Return maximum of two numbers. + max = x: y: if x > y then x else y; + + /* + Integer modulus + + Example: + mod 11 10 + => 1 + mod 1 10 + => 1 + */ + mod = base: int: base - (int * (builtins.div base int)); + + ## Comparisons + + /* + C-style comparisons + + a < b, compare a b => -1 + a == b, compare a b => 0 + a > b, compare a b => 1 + */ + compare = + a: b: + if a < b then + -1 + else if a > b then + 1 + else + 0; + + /* + Split type into two subtypes by predicate `p`, take all elements + of the first subtype to be less than all the elements of the + second subtype, compare elements of a single subtype with `yes` + and `no` respectively. + + Type: (a -> bool) -> (a -> a -> int) -> (a -> a -> int) -> (a -> a -> int) + + Example: + let cmp = splitByAndCompare (hasPrefix "foo") compare compare; in + + cmp "a" "z" => -1 + cmp "fooa" "fooz" => -1 + + cmp "f" "a" => 1 + cmp "fooa" "a" => -1 + # while + compare "fooa" "a" => 1 + */ + splitByAndCompare = + # Predicate + p: + # Comparison function if predicate holds for both values + yes: + # Comparison function if predicate holds for neither value + no: + # First value to compare + a: + # Second value to compare + b: + if p a then + if p b then yes a b else -1 + else if p b then + 1 + else + no a b; + + /* + Reads a JSON file. + + Type :: path -> any + */ + importJSON = path: builtins.fromJSON (builtins.readFile path); + + /* + Reads a TOML file. + + Type :: path -> any + */ + importTOML = path: builtins.fromTOML (builtins.readFile path); + + ## Warnings + + # See https://github.com/NixOS/nix/issues/749. Eventually we'd like these + # to expand to Nix builtins that carry metadata so that Nix can filter out + # the INFO messages without parsing the message string. + # + # Usage: + # { + # foo = lib.warn "foo is deprecated" oldFoo; + # bar = lib.warnIf (bar == "") "Empty bar is deprecated" bar; + # } + # + # TODO: figure out a clever way to integrate location information from + # something like __unsafeGetAttrPos. + + /* + Print a warning before returning the second argument. This function behaves + like `builtins.trace`, but requires a string message and formats it as a + warning, including the `warning: ` prefix. + + To get a call stack trace and abort evaluation, set the environment variable + `NIX_ABORT_ON_WARN=true` and set the Nix options `--option pure-eval false --show-trace` + + Type: string -> a -> a + */ + warn = + if + lib.elem (builtins.getEnv "NIX_ABORT_ON_WARN") [ + "1" + "true" + "yes" + ] + then + msg: + builtins.trace "warning: ${msg}" ( + abort "NIX_ABORT_ON_WARN=true; warnings are treated as unrecoverable errors." + ) + else + msg: builtins.trace "warning: ${msg}"; + + /* + Like warn, but only warn when the first argument is `true`. + + Type: bool -> string -> a -> a + */ + warnIf = cond: msg: if cond then warn msg else id; + + /* + Like the `assert b; e` expression, but with a custom error message and + without the semicolon. + + If true, return the identity function, `r: r`. + + If false, throw the error message. + + Calls can be juxtaposed using function application, as `(r: r) a = a`, so + `(r: r) (r: r) a = a`, and so forth. + + Type: bool -> string -> a -> a + + Example: + + throwIfNot (lib.isList overlays) "The overlays argument to nixpkgs must be a list." + lib.foldr (x: throwIfNot (lib.isFunction x) "All overlays passed to nixpkgs must be functions.") (r: r) overlays + pkgs + */ + throwIfNot = cond: msg: if cond then x: x else throw msg; + + /* + Check if the elements in a list are valid values from a enum, returning the identity function, or throwing an error message otherwise. + + Example: + let colorVariants = ["bright" "dark" "black"] + in checkListOfEnum "color variants" [ "standard" "light" "dark" ] colorVariants; + => + error: color variants: bright, black unexpected; valid ones: standard, light, dark + + Type: String -> List ComparableVal -> List ComparableVal -> a -> a + */ + checkListOfEnum = + msg: valid: given: + let + unexpected = lib.subtractLists valid given; + in + lib.throwIfNot (unexpected == [ ]) + "${msg}: ${builtins.concatStringsSep ", " (builtins.map builtins.toString unexpected)} unexpected; valid ones: ${builtins.concatStringsSep ", " (builtins.map builtins.toString valid)}"; + + info = msg: builtins.trace "INFO: ${msg}"; + + showWarnings = warnings: res: lib.foldr (w: x: warn w x) res warnings; + + ## Function annotations + + /* + Add metadata about expected function arguments to a function. + The metadata should match the format given by + builtins.functionArgs, i.e. a set from expected argument to a bool + representing whether that argument has a default or not. + setFunctionArgs : (a → b) → Map String Bool → (a → b) + + This function is necessary because you can't dynamically create a + function of the { a, b ? foo, ... }: format, but some facilities + like callPackage expect to be able to query expected arguments. + */ + setFunctionArgs = f: args: { + # TODO: Should we add call-time "type" checking like built in? + __functor = self: f; + __functionArgs = args; + }; + + /* + Extract the expected function arguments from a function. + This works both with nix-native { a, b ? foo, ... }: style + functions and functions with args set with 'setFunctionArgs'. It + has the same return type and semantics as builtins.functionArgs. + setFunctionArgs : (a → b) → Map String Bool. + */ + functionArgs = + f: + if f ? __functor then + f.__functionArgs or (lib.functionArgs (f.__functor f)) + else + builtins.functionArgs f; + + /* + Check whether something is a function or something + annotated with function args. + */ + isFunction = + f: builtins.isFunction f || (f ? __functor && isFunction (f.__functor f)); + + /* + Convert the given positive integer to a string of its hexadecimal + representation. For example: + + toHexString 0 => "0" + + toHexString 16 => "10" + + toHexString 250 => "FA" + */ + toHexString = + i: + let + toHexDigit = + d: + if d < 10 then + toString d + else + { + "10" = "A"; + "11" = "B"; + "12" = "C"; + "13" = "D"; + "14" = "E"; + "15" = "F"; + } + .${toString d}; + in + lib.concatMapStrings toHexDigit (toBaseDigits 16 i); + + /* + `toBaseDigits base i` converts the positive integer i to a list of its + digits in the given base. For example: + + toBaseDigits 10 123 => [ 1 2 3 ] + + toBaseDigits 2 6 => [ 1 1 0 ] + + toBaseDigits 16 250 => [ 15 10 ] + */ + toBaseDigits = + base: i: + let + go = + i: + if i < base then + [ i ] + else + let + r = i - ((i / base) * base); + q = (i - r) / base; + in + [ r ] ++ go q; + in + assert (base >= 2); + assert (i >= 0); + lib.reverseList (go i); +} diff --git a/test/diff/idioms_lib_3/out-pure.nix b/test/diff/idioms_lib_3/out-pure.nix new file mode 100644 index 00000000..1115ae8b --- /dev/null +++ b/test/diff/idioms_lib_3/out-pure.nix @@ -0,0 +1,569 @@ +# Functions that generate widespread file +# formats from nix data structures. +# +# They all follow a similar interface: +# generator { config-attrs } data +# +# `config-attrs` are “holes” in the generators +# with sensible default implementations that +# can be overwritten. The default implementations +# are mostly generators themselves, called with +# their respective default values; they can be reused. +# +# Tests can be found in ./tests/misc.nix +# Documentation in the manual, #sec-generators +{ lib }: +with (lib).trivial; +let + libStr = lib.strings; + libAttr = lib.attrsets; + + inherit (lib) isFunction; + +in +rec { + + ## -- HELPER FUNCTIONS & DEFAULTS -- + + # Convert a value to a sensible default string representation. + # The builtin `toString` function has some strange defaults, + # suitable for bash scripts but not much else. + mkValueStringDefault = + { }: + v: + with builtins; + let + err = + t: v: + abort ( + "generators.mkValueStringDefault: " + "${t} not supported: ${toPretty { } v}" + ); + in + if isInt v then + toString v + # convert derivations to store paths + else if lib.isDerivation v then + toString v + # we default to not quoting strings + else if isString v then + v + # isString returns "1", which is not a good default + else if true == v then + "true" + # here it returns to "", which is even less of a good default + else if false == v then + "false" + else if null == v then + "null" + # if you have lists you probably want to replace this + else if isList v then + err "lists" v + # same as for lists, might want to replace + else if isAttrs v then + err "attrsets" v + # functions can’t be printed of course + else if isFunction v then + err "functions" v + # Floats currently can't be converted to precise strings, + # condition warning on nix version once this isn't a problem anymore + # See https://github.com/NixOS/nix/pull/3480 + else if isFloat v then + libStr.floatToString v + else + err "this value is" (toString v); + + # Generate a line of key k and value v, separated by + # character sep. If sep appears in k, it is escaped. + # Helper for synaxes with different separators. + # + # mkValueString specifies how values should be formatted. + # + # mkKeyValueDefault {} ":" "f:oo" "bar" + # > "f\:oo:bar" + mkKeyValueDefault = + { + mkValueString ? mkValueStringDefault { }, + }: + sep: k: v: + "${libStr.escape [ sep ] k}${sep}${mkValueString v}"; + + ## -- FILE FORMAT GENERATORS -- + + # Generate a key-value-style config file from an attrset. + # + # mkKeyValue is the same as in toINI. + toKeyValue = + { + mkKeyValue ? mkKeyValueDefault { } "=", + listsAsDuplicateKeys ? false, + }: + let + mkLine = k: v: mkKeyValue k v + "\n"; + mkLines = + if listsAsDuplicateKeys then + k: v: map (mkLine k) (if lib.isList v then v else [ v ]) + else + k: v: [ (mkLine k v) ]; + in + attrs: + libStr.concatStrings (lib.concatLists (libAttr.mapAttrsToList mkLines attrs)); + + # Generate an INI-style config file from an + # attrset of sections to an attrset of key-value pairs. + # + # generators.toINI {} { + # foo = { hi = "${pkgs.hello}"; ciao = "bar"; }; + # baz = { "also, integers" = 42; }; + # } + # + #> [baz] + #> also, integers=42 + #> + #> [foo] + #> ciao=bar + #> hi=/nix/store/y93qql1p5ggfnaqjjqhxcw0vqw95rlz0-hello-2.10 + # + # The mk* configuration attributes can generically change + # the way sections and key-value strings are generated. + # + # For more examples see the test cases in ./tests/misc.nix. + toINI = + { + # apply transformations (e.g. escapes) to section names + mkSectionName ? ( + name: + libStr.escape [ + "[" + "]" + ] name + ), + # format a setting line from key and value + mkKeyValue ? mkKeyValueDefault { } "=", + # allow lists as values for duplicate keys + listsAsDuplicateKeys ? false, + }: + attrsOfAttrs: + let + # map function to string for each key val + mapAttrsToStringsSep = + sep: mapFn: attrs: + libStr.concatStringsSep sep (libAttr.mapAttrsToList mapFn attrs); + mkSection = + sectName: sectValues: + '' + [${mkSectionName sectName}] + '' + + toKeyValue { inherit mkKeyValue listsAsDuplicateKeys; } sectValues; + in + # map input to ini sections + mapAttrsToStringsSep "\n" mkSection attrsOfAttrs; + + # Generate an INI-style config file from an attrset + # specifying the global section (no header), and an + # attrset of sections to an attrset of key-value pairs. + # + # generators.toINIWithGlobalSection {} { + # globalSection = { + # someGlobalKey = "hi"; + # }; + # sections = { + # foo = { hi = "${pkgs.hello}"; ciao = "bar"; }; + # baz = { "also, integers" = 42; }; + # } + # + #> someGlobalKey=hi + #> + #> [baz] + #> also, integers=42 + #> + #> [foo] + #> ciao=bar + #> hi=/nix/store/y93qql1p5ggfnaqjjqhxcw0vqw95rlz0-hello-2.10 + # + # The mk* configuration attributes can generically change + # the way sections and key-value strings are generated. + # + # For more examples see the test cases in ./tests/misc.nix. + # + # If you don’t need a global section, you can also use + # `generators.toINI` directly, which only takes + # the part in `sections`. + toINIWithGlobalSection = + { + # apply transformations (e.g. escapes) to section names + mkSectionName ? ( + name: + libStr.escape [ + "[" + "]" + ] name + ), + # format a setting line from key and value + mkKeyValue ? mkKeyValueDefault { } "=", + # allow lists as values for duplicate keys + listsAsDuplicateKeys ? false, + }: + { globalSection, sections }: + ( + if globalSection == { } then + "" + else + (toKeyValue { inherit mkKeyValue listsAsDuplicateKeys; } globalSection) + "\n" + ) + + (toINI { inherit mkSectionName mkKeyValue listsAsDuplicateKeys; } sections); + + # Generate a git-config file from an attrset. + # + # It has two major differences from the regular INI format: + # + # 1. values are indented with tabs + # 2. sections can have sub-sections + # + # generators.toGitINI { + # url."ssh://git@github.com/".insteadOf = "https://github.com"; + # user.name = "edolstra"; + # } + # + #> [url "ssh://git@github.com/"] + #> insteadOf = https://github.com/ + #> + #> [user] + #> name = edolstra + toGitINI = + attrs: + with builtins; + let + mkSectionName = + name: + let + containsQuote = libStr.hasInfix ''"'' name; + sections = libStr.splitString "." name; + section = head sections; + subsections = tail sections; + subsection = concatStringsSep "." subsections; + in + if containsQuote || subsections == [ ] then + name + else + ''${section} "${subsection}"''; + + # generation for multiple ini values + mkKeyValue = + k: v: + let + mkKeyValue = mkKeyValueDefault { } " = " k; + in + concatStringsSep "\n" (map (kv: " " + mkKeyValue kv) (lib.toList v)); + + # converts { a.b.c = 5; } to { "a.b".c = 5; } for toINI + gitFlattenAttrs = + let + recurse = + path: value: + if isAttrs value && !lib.isDerivation value then + lib.mapAttrsToList (name: value: recurse ([ name ] ++ path) value) value + else if length path > 1 then + { ${concatStringsSep "." (lib.reverseList (tail path))}.${head path} = value; } + else + { ${head path} = value; }; + in + attrs: lib.foldl lib.recursiveUpdate { } (lib.flatten (recurse [ ] attrs)); + + toINI_ = toINI { inherit mkKeyValue mkSectionName; }; + in + toINI_ (gitFlattenAttrs attrs); + + # Generates JSON from an arbitrary (non-function) value. + # For more information see the documentation of the builtin. + toJSON = { }: builtins.toJSON; + + # YAML has been a strict superset of JSON since 1.2, so we + # use toJSON. Before it only had a few differences referring + # to implicit typing rules, so it should work with older + # parsers as well. + toYAML = toJSON; + + withRecursion = + { + # If this option is not null, the given value will stop evaluating at a certain depth + depthLimit, + # If this option is true, an error will be thrown, if a certain given depth is exceeded + throwOnDepthLimit ? true, + }: + assert builtins.isInt depthLimit; + let + specialAttrs = [ + "__functor" + "__functionArgs" + "__toString" + "__pretty" + ]; + stepIntoAttr = + evalNext: name: if builtins.elem name specialAttrs then id else evalNext; + transform = + depth: + if depthLimit != null && depth > depthLimit then + if throwOnDepthLimit then + throw "Exceeded maximum eval-depth limit of ${toString depthLimit} while trying to evaluate with `generators.withRecursion'!" + else + const "" + else + id; + mapAny = + with builtins; + depth: v: + let + evalNext = x: mapAny (depth + 1) (transform (depth + 1) x); + in + if isAttrs v then + mapAttrs (stepIntoAttr evalNext) v + else if isList v then + map evalNext v + else + transform (depth + 1) v; + in + mapAny 0; + + # Pretty print a value, akin to `builtins.trace`. + # Should probably be a builtin as well. + # The pretty-printed string should be suitable for rendering default values + # in the NixOS manual. In particular, it should be as close to a valid Nix expression + # as possible. + toPretty = + { + /* + If this option is true, attrsets like { __pretty = fn; val = …; } + will use fn to convert val to a pretty printed representation. + (This means fn is type Val -> String.) + */ + allowPrettyValues ? false, + # If this option is true, the output is indented with newlines for attribute sets and lists + multiline ? true, + # Initial indentation level + indent ? "", + }: + let + go = + indent: v: + with builtins; + let + isPath = v: typeOf v == "path"; + introSpace = + if multiline then + '' + + ${indent} '' + else + " "; + outroSpace = + if multiline then + '' + + ${indent}'' + else + " "; + in + if isInt v then + toString v + # toString loses precision on floats, so we use toJSON instead. This isn't perfect + # as the resulting string may not parse back as a float (e.g. 42, 1e-06), but for + # pretty-printing purposes this is acceptable. + else if isFloat v then + builtins.toJSON v + else if isString v then + let + lines = filter (v: !isList v) (builtins.split "\n" v); + escapeSingleline = libStr.escape [ + "\\" + ''"'' + "\${" + ]; + escapeMultiline = + libStr.replaceStrings + [ + "\${" + "''" + ] + [ + "''\${" + "'''" + ]; + singlelineResult = + ''"'' + concatStringsSep "\\n" (map escapeSingleline lines) + ''"''; + multilineResult = + let + escapedLines = map escapeMultiline lines; + # The last line gets a special treatment: if it's empty, '' is on its own line at the "outer" + # indentation level. Otherwise, '' is appended to the last line. + lastLine = lib.last escapedLines; + in + "''" + + introSpace + + concatStringsSep introSpace (lib.init escapedLines) + + (if lastLine == "" then outroSpace else introSpace + lastLine) + + "''"; + in + if multiline && length lines > 1 then multilineResult else singlelineResult + else if true == v then + "true" + else if false == v then + "false" + else if null == v then + "null" + else if isPath v then + toString v + else if isList v then + if v == [ ] then + "[ ]" + else + "[" + + introSpace + + libStr.concatMapStringsSep introSpace (go (indent + " ")) v + + outroSpace + + "]" + else if isFunction v then + let + fna = lib.functionArgs v; + showFnas = concatStringsSep ", " ( + libAttr.mapAttrsToList ( + name: hasDefVal: if hasDefVal then name + "?" else name + ) fna + ); + in + if fna == { } then "" else "" + else if isAttrs v then + # apply pretty values if allowed + if allowPrettyValues && v ? __pretty && v ? val then + v.__pretty v.val + else if v == { } then + "{ }" + else if v ? type && v.type == "derivation" then + "" + else + "{" + + introSpace + + libStr.concatStringsSep introSpace ( + libAttr.mapAttrsToList ( + name: value: + "${libStr.escapeNixIdentifier name} = ${ + builtins.addErrorContext "while evaluating an attribute `${name}`" ( + go (indent + " ") value + ) + };" + ) v + ) + + outroSpace + + "}" + else + abort "generators.toPretty: should never happen (v = ${v})"; + in + go indent; + + # PLIST handling + toPlist = + { }: + v: + let + isFloat = builtins.isFloat or (x: false); + expr = + ind: x: + with builtins; + if x == null then + "" + else if isBool x then + bool ind x + else if isInt x then + int ind x + else if isString x then + str ind x + else if isList x then + list ind x + else if isAttrs x then + attrs ind x + else if isFloat x then + float ind x + else + abort "generators.toPlist: should never happen (v = ${v})"; + + literal = ind: x: ind + x; + + bool = ind: x: literal ind (if x then "" else ""); + int = ind: x: literal ind "${toString x}"; + str = ind: x: literal ind "${x}"; + key = ind: x: literal ind "${x}"; + float = ind: x: literal ind "${toString x}"; + + indent = ind: expr " ${ind}"; + + item = ind: libStr.concatMapStringsSep "\n" (indent ind); + + list = + ind: x: + libStr.concatStringsSep "\n" [ + (literal ind "") + (item ind x) + (literal ind "") + ]; + + attrs = + ind: x: + libStr.concatStringsSep "\n" [ + (literal ind "") + (attr ind x) + (literal ind "") + ]; + + attr = + let + attrFilter = name: value: name != "_module" && value != null; + in + ind: x: + libStr.concatStringsSep "\n" ( + lib.flatten ( + lib.mapAttrsToList ( + name: value: + lib.optionals (attrFilter name value) [ + (key " ${ind}" name) + (expr " ${ind}" value) + ] + ) x + ) + ); + + in + '' + + + + ${expr "" v} + ''; + + # Translate a simple Nix expression to Dhall notation. + # Note that integers are translated to Integer and never + # the Natural type. + toDhall = + { }@args: + v: + with builtins; + let + concatItems = lib.strings.concatStringsSep ", "; + in + if isAttrs v then + "{ ${ + concatItems ( + lib.attrsets.mapAttrsToList (key: value: "${key} = ${toDhall args value}") v + ) + } }" + else if isList v then + "[ ${concatItems (map (toDhall args) v)} ]" + else if isInt v then + "${if v < 0 then "" else "+"}${toString v}" + else if isBool v then + (if v then "True" else "False") + else if isFunction v then + abort "generators.toDhall: cannot convert a function to Dhall" + else if v == null then + abort "generators.toDhall: cannot convert a null to Dhall" + else + builtins.toJSON v; +} diff --git a/test/diff/idioms_lib_3/out.nix b/test/diff/idioms_lib_3/out.nix index 1115ae8b..4a1b2843 100644 --- a/test/diff/idioms_lib_3/out.nix +++ b/test/diff/idioms_lib_3/out.nix @@ -12,7 +12,9 @@ # # Tests can be found in ./tests/misc.nix # Documentation in the manual, #sec-generators -{ lib }: +{ + lib, +}: with (lib).trivial; let libStr = lib.strings; @@ -29,7 +31,8 @@ rec { # The builtin `toString` function has some strange defaults, # suitable for bash scripts but not much else. mkValueStringDefault = - { }: + { + }: v: with builtins; let @@ -203,7 +206,10 @@ rec { # allow lists as values for duplicate keys listsAsDuplicateKeys ? false, }: - { globalSection, sections }: + { + globalSection, + sections, + }: ( if globalSection == { } then "" @@ -263,9 +269,13 @@ rec { if isAttrs value && !lib.isDerivation value then lib.mapAttrsToList (name: value: recurse ([ name ] ++ path) value) value else if length path > 1 then - { ${concatStringsSep "." (lib.reverseList (tail path))}.${head path} = value; } + { + ${concatStringsSep "." (lib.reverseList (tail path))}.${head path} = value; + } else - { ${head path} = value; }; + { + ${head path} = value; + }; in attrs: lib.foldl lib.recursiveUpdate { } (lib.flatten (recurse [ ] attrs)); @@ -275,7 +285,10 @@ rec { # Generates JSON from an arbitrary (non-function) value. # For more information see the documentation of the builtin. - toJSON = { }: builtins.toJSON; + toJSON = + { + }: + builtins.toJSON; # YAML has been a strict superset of JSON since 1.2, so we # use toJSON. Before it only had a few differences referring @@ -461,7 +474,8 @@ rec { # PLIST handling toPlist = - { }: + { + }: v: let isFloat = builtins.isFloat or (x: false); @@ -542,7 +556,8 @@ rec { # Note that integers are translated to Integer and never # the Natural type. toDhall = - { }@args: + { + }@args: v: with builtins; let diff --git a/test/diff/idioms_lib_4/out-pure.nix b/test/diff/idioms_lib_4/out-pure.nix new file mode 100644 index 00000000..8ff78dae --- /dev/null +++ b/test/diff/idioms_lib_4/out-pure.nix @@ -0,0 +1,933 @@ +# Define the list of system with their properties. +# +# See https://clang.llvm.org/docs/CrossCompilation.html and +# http://llvm.org/docs/doxygen/html/Triple_8cpp_source.html especially +# Triple::normalize. Parsing should essentially act as a more conservative +# version of that last function. +# +# Most of the types below come in "open" and "closed" pairs. The open ones +# specify what information we need to know about systems in general, and the +# closed ones are sub-types representing the whitelist of systems we support in +# practice. +# +# Code in the remainder of nixpkgs shouldn't rely on the closed ones in +# e.g. exhaustive cases. Its more a sanity check to make sure nobody defines +# systems that overlap with existing ones and won't notice something amiss. +# +{ lib }: +with lib.lists; +with lib.types; +with lib.attrsets; +with lib.strings; +with (import ./inspect.nix { inherit lib; }).predicates; + +let + inherit (lib.options) mergeOneOption; + + setTypes = + type: + mapAttrs ( + name: value: + assert type.check value; + setType type.name ({ inherit name; } // value) + ); + +in + +rec { + + ################################################################################ + + types.openSignificantByte = mkOptionType { + name = "significant-byte"; + description = "Endianness"; + merge = mergeOneOption; + }; + + types.significantByte = enum (attrValues significantBytes); + + significantBytes = setTypes types.openSignificantByte { + bigEndian = { }; + littleEndian = { }; + }; + + ################################################################################ + + # Reasonable power of 2 + types.bitWidth = enum [ + 8 + 16 + 32 + 64 + 128 + ]; + + ################################################################################ + + types.openCpuType = mkOptionType { + name = "cpu-type"; + description = "instruction set architecture name and information"; + merge = mergeOneOption; + check = + x: + types.bitWidth.check x.bits + && ( + if 8 < x.bits then + types.significantByte.check x.significantByte + else + !(x ? significantByte) + ); + }; + + types.cpuType = enum (attrValues cpuTypes); + + cpuTypes = + with significantBytes; + setTypes types.openCpuType { + arm = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + }; + armv5tel = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "5"; + arch = "armv5t"; + }; + armv6m = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "6"; + arch = "armv6-m"; + }; + armv6l = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "6"; + arch = "armv6"; + }; + armv7a = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "7"; + arch = "armv7-a"; + }; + armv7r = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "7"; + arch = "armv7-r"; + }; + armv7m = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "7"; + arch = "armv7-m"; + }; + armv7l = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "7"; + arch = "armv7"; + }; + armv8a = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "8"; + arch = "armv8-a"; + }; + armv8r = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "8"; + arch = "armv8-a"; + }; + armv8m = { + bits = 32; + significantByte = littleEndian; + family = "arm"; + version = "8"; + arch = "armv8-m"; + }; + aarch64 = { + bits = 64; + significantByte = littleEndian; + family = "arm"; + version = "8"; + arch = "armv8-a"; + }; + aarch64_be = { + bits = 64; + significantByte = bigEndian; + family = "arm"; + version = "8"; + arch = "armv8-a"; + }; + + i386 = { + bits = 32; + significantByte = littleEndian; + family = "x86"; + arch = "i386"; + }; + i486 = { + bits = 32; + significantByte = littleEndian; + family = "x86"; + arch = "i486"; + }; + i586 = { + bits = 32; + significantByte = littleEndian; + family = "x86"; + arch = "i586"; + }; + i686 = { + bits = 32; + significantByte = littleEndian; + family = "x86"; + arch = "i686"; + }; + x86_64 = { + bits = 64; + significantByte = littleEndian; + family = "x86"; + arch = "x86-64"; + }; + + microblaze = { + bits = 32; + significantByte = bigEndian; + family = "microblaze"; + }; + microblazeel = { + bits = 32; + significantByte = littleEndian; + family = "microblaze"; + }; + + mips = { + bits = 32; + significantByte = bigEndian; + family = "mips"; + }; + mipsel = { + bits = 32; + significantByte = littleEndian; + family = "mips"; + }; + mips64 = { + bits = 64; + significantByte = bigEndian; + family = "mips"; + }; + mips64el = { + bits = 64; + significantByte = littleEndian; + family = "mips"; + }; + + mmix = { + bits = 64; + significantByte = bigEndian; + family = "mmix"; + }; + + m68k = { + bits = 32; + significantByte = bigEndian; + family = "m68k"; + }; + + powerpc = { + bits = 32; + significantByte = bigEndian; + family = "power"; + }; + powerpc64 = { + bits = 64; + significantByte = bigEndian; + family = "power"; + }; + powerpc64le = { + bits = 64; + significantByte = littleEndian; + family = "power"; + }; + powerpcle = { + bits = 32; + significantByte = littleEndian; + family = "power"; + }; + + riscv32 = { + bits = 32; + significantByte = littleEndian; + family = "riscv"; + }; + riscv64 = { + bits = 64; + significantByte = littleEndian; + family = "riscv"; + }; + + s390 = { + bits = 32; + significantByte = bigEndian; + family = "s390"; + }; + s390x = { + bits = 64; + significantByte = bigEndian; + family = "s390"; + }; + + sparc = { + bits = 32; + significantByte = bigEndian; + family = "sparc"; + }; + sparc64 = { + bits = 64; + significantByte = bigEndian; + family = "sparc"; + }; + + wasm32 = { + bits = 32; + significantByte = littleEndian; + family = "wasm"; + }; + wasm64 = { + bits = 64; + significantByte = littleEndian; + family = "wasm"; + }; + + alpha = { + bits = 64; + significantByte = littleEndian; + family = "alpha"; + }; + + rx = { + bits = 32; + significantByte = littleEndian; + family = "rx"; + }; + msp430 = { + bits = 16; + significantByte = littleEndian; + family = "msp430"; + }; + avr = { + bits = 8; + family = "avr"; + }; + + vc4 = { + bits = 32; + significantByte = littleEndian; + family = "vc4"; + }; + + or1k = { + bits = 32; + significantByte = bigEndian; + family = "or1k"; + }; + + loongarch64 = { + bits = 64; + significantByte = littleEndian; + family = "loongarch"; + }; + + javascript = { + bits = 32; + significantByte = littleEndian; + family = "javascript"; + }; + }; + + # GNU build systems assume that older NetBSD architectures are using a.out. + gnuNetBSDDefaultExecFormat = + cpu: + if + (cpu.family == "arm" && cpu.bits == 32) + || (cpu.family == "sparc" && cpu.bits == 32) + || (cpu.family == "m68k" && cpu.bits == 32) + || (cpu.family == "x86" && cpu.bits == 32) + then + execFormats.aout + else + execFormats.elf; + + # Determine when two CPUs are compatible with each other. That is, + # can code built for system B run on system A? For that to happen, + # the programs that system B accepts must be a subset of the + # programs that system A accepts. + # + # We have the following properties of the compatibility relation, + # which must be preserved when adding compatibility information for + # additional CPUs. + # - (reflexivity) + # Every CPU is compatible with itself. + # - (transitivity) + # If A is compatible with B and B is compatible with C then A is compatible with C. + # + # Note: Since 22.11 the archs of a mode switching CPU are no longer considered + # pairwise compatible. Mode switching implies that binaries built for A + # and B respectively can't be executed at the same time. + isCompatible = + a: b: + with cpuTypes; + lib.any lib.id [ + # x86 + (b == i386 && isCompatible a i486) + (b == i486 && isCompatible a i586) + (b == i586 && isCompatible a i686) + + # XXX: Not true in some cases. Like in WSL mode. + (b == i686 && isCompatible a x86_64) + + # ARMv4 + (b == arm && isCompatible a armv5tel) + + # ARMv5 + (b == armv5tel && isCompatible a armv6l) + + # ARMv6 + (b == armv6l && isCompatible a armv6m) + (b == armv6m && isCompatible a armv7l) + + # ARMv7 + (b == armv7l && isCompatible a armv7a) + (b == armv7l && isCompatible a armv7r) + (b == armv7l && isCompatible a armv7m) + + # ARMv8 + (b == aarch64 && a == armv8a) + (b == armv8a && isCompatible a aarch64) + (b == armv8r && isCompatible a armv8a) + (b == armv8m && isCompatible a armv8a) + + # PowerPC + (b == powerpc && isCompatible a powerpc64) + (b == powerpcle && isCompatible a powerpc64le) + + # MIPS + (b == mips && isCompatible a mips64) + (b == mipsel && isCompatible a mips64el) + + # RISCV + (b == riscv32 && isCompatible a riscv64) + + # SPARC + (b == sparc && isCompatible a sparc64) + + # WASM + (b == wasm32 && isCompatible a wasm64) + + # identity + (b == a) + ]; + + ################################################################################ + + types.openVendor = mkOptionType { + name = "vendor"; + description = "vendor for the platform"; + merge = mergeOneOption; + }; + + types.vendor = enum (attrValues vendors); + + vendors = setTypes types.openVendor { + apple = { }; + pc = { }; + # Actually matters, unlocking some MinGW-w64-specific options in GCC. See + # bottom of https://sourceforge.net/p/mingw-w64/wiki2/Unicode%20apps/ + w64 = { }; + + none = { }; + unknown = { }; + }; + + ################################################################################ + + types.openExecFormat = mkOptionType { + name = "exec-format"; + description = "executable container used by the kernel"; + merge = mergeOneOption; + }; + + types.execFormat = enum (attrValues execFormats); + + execFormats = setTypes types.openExecFormat { + aout = { }; # a.out + elf = { }; + macho = { }; + pe = { }; + wasm = { }; + + unknown = { }; + }; + + ################################################################################ + + types.openKernelFamily = mkOptionType { + name = "exec-format"; + description = "executable container used by the kernel"; + merge = mergeOneOption; + }; + + types.kernelFamily = enum (attrValues kernelFamilies); + + kernelFamilies = setTypes types.openKernelFamily { + bsd = { }; + darwin = { }; + }; + + ################################################################################ + + types.openKernel = mkOptionType { + name = "kernel"; + description = "kernel name and information"; + merge = mergeOneOption; + check = + x: + types.execFormat.check x.execFormat + && all types.kernelFamily.check (attrValues x.families); + }; + + types.kernel = enum (attrValues kernels); + + kernels = + with execFormats; + with kernelFamilies; + setTypes types.openKernel { + # TODO(@Ericson2314): Don't want to mass-rebuild yet to keeping 'darwin' as + # the normalized name for macOS. + macos = { + execFormat = macho; + families = { + inherit darwin; + }; + name = "darwin"; + }; + ios = { + execFormat = macho; + families = { + inherit darwin; + }; + }; + # A tricky thing about FreeBSD is that there is no stable ABI across + # versions. That means that putting in the version as part of the + # config string is paramount. + freebsd12 = { + execFormat = elf; + families = { + inherit bsd; + }; + name = "freebsd"; + version = 12; + }; + freebsd13 = { + execFormat = elf; + families = { + inherit bsd; + }; + name = "freebsd"; + version = 13; + }; + linux = { + execFormat = elf; + families = { }; + }; + netbsd = { + execFormat = elf; + families = { + inherit bsd; + }; + }; + none = { + execFormat = unknown; + families = { }; + }; + openbsd = { + execFormat = elf; + families = { + inherit bsd; + }; + }; + solaris = { + execFormat = elf; + families = { }; + }; + wasi = { + execFormat = wasm; + families = { }; + }; + redox = { + execFormat = elf; + families = { }; + }; + windows = { + execFormat = pe; + families = { }; + }; + ghcjs = { + execFormat = unknown; + families = { }; + }; + genode = { + execFormat = elf; + families = { }; + }; + mmixware = { + execFormat = unknown; + families = { }; + }; + } + // { + # aliases + # 'darwin' is the kernel for all of them. We choose macOS by default. + darwin = kernels.macos; + watchos = kernels.ios; + tvos = kernels.ios; + win32 = kernels.windows; + }; + + ################################################################################ + + types.openAbi = mkOptionType { + name = "abi"; + description = "binary interface for compiled code and syscalls"; + merge = mergeOneOption; + }; + + types.abi = enum (attrValues abis); + + abis = setTypes types.openAbi { + cygnus = { }; + msvc = { }; + + # Note: eabi is specific to ARM and PowerPC. + # On PowerPC, this corresponds to PPCEABI. + # On ARM, this corresponds to ARMEABI. + eabi = { + float = "soft"; + }; + eabihf = { + float = "hard"; + }; + + # Other architectures should use ELF in embedded situations. + elf = { }; + + androideabi = { }; + android = { + assertions = [ + { + assertion = platform: !platform.isAarch32; + message = '' + The "android" ABI is not for 32-bit ARM. Use "androideabi" instead. + ''; + } + ]; + }; + + gnueabi = { + float = "soft"; + }; + gnueabihf = { + float = "hard"; + }; + gnu = { + assertions = [ + { + assertion = platform: !platform.isAarch32; + message = '' + The "gnu" ABI is ambiguous on 32-bit ARM. Use "gnueabi" or "gnueabihf" instead. + ''; + } + { + assertion = platform: with platform; !(isPower64 && isBigEndian); + message = '' + The "gnu" ABI is ambiguous on big-endian 64-bit PowerPC. Use "gnuabielfv2" or "gnuabielfv1" instead. + ''; + } + ]; + }; + gnuabi64 = { + abi = "64"; + }; + muslabi64 = { + abi = "64"; + }; + + # NOTE: abi=n32 requires a 64-bit MIPS chip! That is not a typo. + # It is basically the 64-bit abi with 32-bit pointers. Details: + # https://www.linux-mips.org/pub/linux/mips/doc/ABI/MIPS-N32-ABI-Handbook.pdf + gnuabin32 = { + abi = "n32"; + }; + muslabin32 = { + abi = "n32"; + }; + + gnuabielfv2 = { + abi = "elfv2"; + }; + gnuabielfv1 = { + abi = "elfv1"; + }; + + musleabi = { + float = "soft"; + }; + musleabihf = { + float = "hard"; + }; + musl = { }; + + uclibceabi = { + float = "soft"; + }; + uclibceabihf = { + float = "hard"; + }; + uclibc = { }; + + unknown = { }; + }; + + ################################################################################ + + types.parsedPlatform = mkOptionType { + name = "system"; + description = "fully parsed representation of llvm- or nix-style platform tuple"; + merge = mergeOneOption; + check = + { + cpu, + vendor, + kernel, + abi, + }: + types.cpuType.check cpu + && types.vendor.check vendor + && types.kernel.check kernel + && types.abi.check abi; + }; + + isSystem = isType "system"; + + mkSystem = + components: + assert types.parsedPlatform.check components; + setType "system" components; + + mkSkeletonFromList = + l: + { + "1" = + if elemAt l 0 == "avr" then + { + cpu = elemAt l 0; + kernel = "none"; + abi = "unknown"; + } + else + throw "Target specification with 1 components is ambiguous"; + "2" = # We only do 2-part hacks for things Nix already supports + if elemAt l 1 == "cygwin" then + { + cpu = elemAt l 0; + kernel = "windows"; + abi = "cygnus"; + } + # MSVC ought to be the default ABI so this case isn't needed. But then it + # becomes difficult to handle the gnu* variants for Aarch32 correctly for + # minGW. So it's easier to make gnu* the default for the MinGW, but + # hack-in MSVC for the non-MinGW case right here. + else if elemAt l 1 == "windows" then + { + cpu = elemAt l 0; + kernel = "windows"; + abi = "msvc"; + } + else if (elemAt l 1) == "elf" then + { + cpu = elemAt l 0; + vendor = "unknown"; + kernel = "none"; + abi = elemAt l 1; + } + else + { + cpu = elemAt l 0; + kernel = elemAt l 1; + }; + "3" = + # cpu-kernel-environment + if + elemAt l 1 == "linux" + || elem (elemAt l 2) [ + "eabi" + "eabihf" + "elf" + "gnu" + ] + then + { + cpu = elemAt l 0; + kernel = elemAt l 1; + abi = elemAt l 2; + vendor = "unknown"; + } + # cpu-vendor-os + else if + elemAt l 1 == "apple" + || elem (elemAt l 2) [ + "wasi" + "redox" + "mmixware" + "ghcjs" + "mingw32" + ] + || hasPrefix "freebsd" (elemAt l 2) + || hasPrefix "netbsd" (elemAt l 2) + || hasPrefix "genode" (elemAt l 2) + then + { + cpu = elemAt l 0; + vendor = elemAt l 1; + kernel = + if elemAt l 2 == "mingw32" then + "windows" # autotools breaks on -gnu for window + else + elemAt l 2; + } + else + throw "Target specification with 3 components is ambiguous"; + "4" = { + cpu = elemAt l 0; + vendor = elemAt l 1; + kernel = elemAt l 2; + abi = elemAt l 3; + }; + } + .${toString (length l)} + or (throw "system string has invalid number of hyphen-separated components"); + + # This should revert the job done by config.guess from the gcc compiler. + mkSystemFromSkeleton = + { + cpu, + # Optional, but fallback too complex for here. + # Inferred below instead. + vendor ? + assert false; + null, + kernel, + # Also inferred below + abi ? + assert false; + null, + }@args: + let + getCpu = name: cpuTypes.${name} or (throw "Unknown CPU type: ${name}"); + getVendor = name: vendors.${name} or (throw "Unknown vendor: ${name}"); + getKernel = name: kernels.${name} or (throw "Unknown kernel: ${name}"); + getAbi = name: abis.${name} or (throw "Unknown ABI: ${name}"); + + parsed = { + cpu = getCpu args.cpu; + vendor = + if args ? vendor then + getVendor args.vendor + else if isDarwin parsed then + vendors.apple + else if isWindows parsed then + vendors.pc + else + vendors.unknown; + kernel = + if hasPrefix "darwin" args.kernel then + getKernel "darwin" + else if hasPrefix "netbsd" args.kernel then + getKernel "netbsd" + else + getKernel args.kernel; + abi = + if args ? abi then + getAbi args.abi + else if isLinux parsed || isWindows parsed then + if isAarch32 parsed then + if lib.versionAtLeast (parsed.cpu.version or "0") "6" then + abis.gnueabihf + else + abis.gnueabi + # Default ppc64 BE to ELFv2 + else if isPower64 parsed && isBigEndian parsed then + abis.gnuabielfv2 + else + abis.gnu + else + abis.unknown; + }; + + in + mkSystem parsed; + + mkSystemFromString = + s: mkSystemFromSkeleton (mkSkeletonFromList (lib.splitString "-" s)); + + kernelName = kernel: kernel.name + toString (kernel.version or ""); + + doubleFromSystem = + { + cpu, + kernel, + abi, + ... + }: + if abi == abis.cygnus then + "${cpu.name}-cygwin" + else if kernel.families ? darwin then + "${cpu.name}-darwin" + else + "${cpu.name}-${kernelName kernel}"; + + tripleFromSystem = + { + cpu, + vendor, + kernel, + abi, + ... + }@sys: + assert isSystem sys; + let + optExecFormat = lib.optionalString ( + kernel.name == "netbsd" && gnuNetBSDDefaultExecFormat cpu != kernel.execFormat + ) kernel.execFormat.name; + optAbi = lib.optionalString (abi != abis.unknown) "-${abi.name}"; + in + "${cpu.name}-${vendor.name}-${kernelName kernel}${optExecFormat}${optAbi}"; + + ################################################################################ + +} diff --git a/test/diff/idioms_lib_5/out-pure.nix b/test/diff/idioms_lib_5/out-pure.nix new file mode 100644 index 00000000..ee898df8 --- /dev/null +++ b/test/diff/idioms_lib_5/out-pure.nix @@ -0,0 +1,613 @@ +# Checks derivation meta and attrs for problems (like brokenness, +# licenses, etc). + +{ + lib, + config, + hostPlatform, +}: + +let + # If we're in hydra, we can dispense with the more verbose error + # messages and make problems easier to spot. + inHydra = config.inHydra or false; + # Allow the user to opt-into additional warnings, e.g. + # import { config = { showDerivationWarnings = [ "maintainerless" ]; }; } + showWarnings = config.showDerivationWarnings; + + getName = + attrs: + attrs.name or ( + "${attrs.pname or "«name-missing»"}-${attrs.version or "«version-missing»"}" + ); + + allowUnfree = + config.allowUnfree || builtins.getEnv "NIXPKGS_ALLOW_UNFREE" == "1"; + + allowNonSource = + let + envVar = builtins.getEnv "NIXPKGS_ALLOW_NONSOURCE"; + in + if envVar != "" then envVar != "0" else config.allowNonSource or true; + + allowlist = config.allowlistedLicenses or config.whitelistedLicenses or [ ]; + blocklist = config.blocklistedLicenses or config.blacklistedLicenses or [ ]; + + areLicenseListsValid = + if lib.mutuallyExclusive allowlist blocklist then + true + else + throw "allowlistedLicenses and blocklistedLicenses are not mutually exclusive."; + + hasLicense = attrs: attrs ? meta.license; + + hasAllowlistedLicense = + assert areLicenseListsValid; + attrs: + hasLicense attrs + && lib.lists.any (l: builtins.elem l allowlist) ( + lib.lists.toList attrs.meta.license + ); + + hasBlocklistedLicense = + assert areLicenseListsValid; + attrs: + hasLicense attrs + && lib.lists.any (l: builtins.elem l blocklist) ( + lib.lists.toList attrs.meta.license + ); + + allowBroken = + config.allowBroken || builtins.getEnv "NIXPKGS_ALLOW_BROKEN" == "1"; + + allowUnsupportedSystem = + config.allowUnsupportedSystem + || builtins.getEnv "NIXPKGS_ALLOW_UNSUPPORTED_SYSTEM" == "1"; + + isUnfree = licenses: lib.lists.any (l: !l.free or true) licenses; + + hasUnfreeLicense = + attrs: hasLicense attrs && isUnfree (lib.lists.toList attrs.meta.license); + + hasNoMaintainers = + attrs: attrs ? meta.maintainers && (lib.length attrs.meta.maintainers) == 0; + + isMarkedBroken = attrs: attrs.meta.broken or false; + + hasUnsupportedPlatform = pkg: !(lib.meta.availableOn hostPlatform pkg); + + isMarkedInsecure = attrs: (attrs.meta.knownVulnerabilities or [ ]) != [ ]; + + # Alow granular checks to allow only some unfree packages + # Example: + # {pkgs, ...}: + # { + # allowUnfree = false; + # allowUnfreePredicate = (x: pkgs.lib.hasPrefix "vscode" x.name); + # } + allowUnfreePredicate = config.allowUnfreePredicate or (x: false); + + # Check whether unfree packages are allowed and if not, whether the + # package has an unfree license and is not explicitly allowed by the + # `allowUnfreePredicate` function. + hasDeniedUnfreeLicense = + attrs: hasUnfreeLicense attrs && !allowUnfree && !allowUnfreePredicate attrs; + + allowInsecureDefaultPredicate = + x: builtins.elem (getName x) (config.permittedInsecurePackages or [ ]); + allowInsecurePredicate = + x: (config.allowInsecurePredicate or allowInsecureDefaultPredicate) x; + + hasAllowedInsecure = + attrs: + !(isMarkedInsecure attrs) + || allowInsecurePredicate attrs + || builtins.getEnv "NIXPKGS_ALLOW_INSECURE" == "1"; + + isNonSource = sourceTypes: lib.lists.any (t: !t.isSource) sourceTypes; + + hasNonSourceProvenance = + attrs: + (attrs ? meta.sourceProvenance) && isNonSource attrs.meta.sourceProvenance; + + # Allow granular checks to allow only some non-source-built packages + # Example: + # { pkgs, ... }: + # { + # allowNonSource = false; + # allowNonSourcePredicate = with pkgs.lib.lists; pkg: !(any (p: !p.isSource && p != lib.sourceTypes.binaryFirmware) pkg.meta.sourceProvenance); + # } + allowNonSourcePredicate = config.allowNonSourcePredicate or (x: false); + + # Check whether non-source packages are allowed and if not, whether the + # package has non-source provenance and is not explicitly allowed by the + # `allowNonSourcePredicate` function. + hasDeniedNonSourceProvenance = + attrs: + hasNonSourceProvenance attrs + && !allowNonSource + && !allowNonSourcePredicate attrs; + + showLicenseOrSourceType = + value: toString (map (v: v.shortName or "unknown") (lib.lists.toList value)); + showLicense = showLicenseOrSourceType; + showSourceType = showLicenseOrSourceType; + + pos_str = meta: meta.position or "«unknown-file»"; + + remediation = { + unfree = remediate_allowlist "Unfree" ( + remediate_predicate "allowUnfreePredicate" + ); + non-source = remediate_allowlist "NonSource" ( + remediate_predicate "allowNonSourcePredicate" + ); + broken = remediate_allowlist "Broken" (x: ""); + unsupported = remediate_allowlist "UnsupportedSystem" (x: ""); + blocklisted = x: ""; + insecure = remediate_insecure; + broken-outputs = remediateOutputsToInstall; + unknown-meta = x: ""; + maintainerless = x: ""; + }; + remediation_env_var = + allow_attr: + { + Unfree = "NIXPKGS_ALLOW_UNFREE"; + Broken = "NIXPKGS_ALLOW_BROKEN"; + UnsupportedSystem = "NIXPKGS_ALLOW_UNSUPPORTED_SYSTEM"; + NonSource = "NIXPKGS_ALLOW_NONSOURCE"; + } + .${allow_attr}; + remediation_phrase = + allow_attr: + { + Unfree = "unfree packages"; + Broken = "broken packages"; + UnsupportedSystem = "packages that are unsupported for this system"; + NonSource = "packages not built from source"; + } + .${allow_attr}; + remediate_predicate = predicateConfigAttr: attrs: '' + + Alternatively you can configure a predicate to allow specific packages: + { nixpkgs.config.${predicateConfigAttr} = pkg: builtins.elem (lib.getName pkg) [ + "${lib.getName attrs}" + ]; + } + ''; + + # flakeNote will be printed in the remediation messages below. + flakeNote = " + Note: For `nix shell`, `nix build`, `nix develop` or any other Nix 2.4+ + (Flake) command, `--impure` must be passed in order to read this + environment variable. + "; + + remediate_allowlist = allow_attr: rebuild_amendment: attrs: '' + a) To temporarily allow ${remediation_phrase allow_attr}, you can use an environment variable + for a single invocation of the nix tools. + + $ export ${remediation_env_var allow_attr}=1 + ${flakeNote} + b) For `nixos-rebuild` you can set + { nixpkgs.config.allow${allow_attr} = true; } + in configuration.nix to override this. + ${rebuild_amendment attrs} + c) For `nix-env`, `nix-build`, `nix-shell` or any other Nix command you can add + { allow${allow_attr} = true; } + to ~/.config/nixpkgs/config.nix. + ''; + + remediate_insecure = + attrs: + '' + + Known issues: + '' + + (lib.concatStrings ( + map (issue: " - ${issue}\n") attrs.meta.knownVulnerabilities + )) + + '' + + You can install it anyway by allowing this package, using the + following methods: + + a) To temporarily allow all insecure packages, you can use an environment + variable for a single invocation of the nix tools: + + $ export NIXPKGS_ALLOW_INSECURE=1 + ${flakeNote} + b) for `nixos-rebuild` you can add ‘${getName attrs}’ to + `nixpkgs.config.permittedInsecurePackages` in the configuration.nix, + like so: + + { + nixpkgs.config.permittedInsecurePackages = [ + "${getName attrs}" + ]; + } + + c) For `nix-env`, `nix-build`, `nix-shell` or any other Nix command you can add + ‘${getName attrs}’ to `permittedInsecurePackages` in + ~/.config/nixpkgs/config.nix, like so: + + { + permittedInsecurePackages = [ + "${getName attrs}" + ]; + } + + ''; + + remediateOutputsToInstall = + attrs: + let + expectedOutputs = attrs.meta.outputsToInstall or [ ]; + actualOutputs = attrs.outputs or [ "out" ]; + missingOutputs = builtins.filter ( + output: !builtins.elem output actualOutputs + ) expectedOutputs; + in + '' + The package ${getName attrs} has set meta.outputsToInstall to: ${builtins.concatStringsSep ", " expectedOutputs} + + however ${getName attrs} only has the outputs: ${builtins.concatStringsSep ", " actualOutputs} + + and is missing the following ouputs: + + ${lib.concatStrings (builtins.map (output: " - ${output}\n") missingOutputs)} + ''; + + handleEvalIssue = + { meta, attrs }: + { + reason, + errormsg ? "", + }: + let + msg = + if inHydra then + "Failed to evaluate ${getName attrs}: «${reason}»: ${errormsg}" + else + '' + Package ‘${getName attrs}’ in ${pos_str meta} ${errormsg}, refusing to evaluate. + + '' + + (builtins.getAttr reason remediation) attrs; + + handler = + if config ? handleEvalIssue then config.handleEvalIssue reason else throw; + in + handler msg; + + handleEvalWarning = + { meta, attrs }: + { + reason, + errormsg ? "", + }: + let + remediationMsg = (builtins.getAttr reason remediation) attrs; + msg = + if inHydra then + "Warning while evaluating ${getName attrs}: «${reason}»: ${errormsg}" + else + "Package ${getName attrs} in ${pos_str meta} ${errormsg}, continuing anyway." + + (lib.optionalString (remediationMsg != "") "\n${remediationMsg}"); + isEnabled = lib.findFirst (x: x == reason) null showWarnings; + in + if isEnabled != null then builtins.trace msg true else true; + + # Deep type-checking. Note that calling `type.check` is not enough: see `lib.mkOptionType`'s documentation. + # We don't include this in lib for now because this function is flawed: it accepts things like `mkIf true 42`. + typeCheck = + type: value: + let + merged = lib.mergeDefinitions [ ] type [ + { + file = lib.unknownModule; + inherit value; + } + ]; + eval = builtins.tryEval (builtins.deepSeq merged.mergedValue null); + in + eval.success; + + # TODO make this into a proper module and use the generic option documentation generation? + metaTypes = with lib.types; rec { + # These keys are documented + description = str; + mainProgram = str; + longDescription = str; + branch = str; + homepage = either (listOf str) str; + downloadPage = str; + changelog = either (listOf str) str; + license = + let + licenseType = either (attrsOf anything) str; # TODO disallow `str` licenses, use a module + in + either licenseType (listOf licenseType); + sourceProvenance = listOf lib.types.attrs; + maintainers = listOf (attrsOf anything); # TODO use the maintainer type from lib/tests/maintainer-module.nix + priority = int; + pkgConfigModules = listOf str; + platforms = listOf (either str (attrsOf anything)); # see lib.meta.platformMatch + hydraPlatforms = listOf str; + broken = bool; + unfree = bool; + unsupported = bool; + insecure = bool; + # TODO: refactor once something like Profpatsch's types-simple will land + # This is currently dead code due to https://github.com/NixOS/nix/issues/2532 + tests = attrsOf (mkOptionType { + name = "test"; + check = + x: + x == { } + || + # Accept {} for tests that are unsupported + (isDerivation x && x ? meta.timeout); + merge = lib.options.mergeOneOption; + }); + timeout = int; + + # Needed for Hydra to expose channel tarballs: + # https://github.com/NixOS/hydra/blob/53335323ae79ca1a42643f58e520b376898ce641/doc/manual/src/jobs.md#meta-fields + isHydraChannel = bool; + + # Weirder stuff that doesn't appear in the documentation? + maxSilent = int; + knownVulnerabilities = listOf str; + name = str; + version = str; + tag = str; + executables = listOf str; + outputsToInstall = listOf str; + position = str; + available = unspecified; + isBuildPythonPackage = platforms; + schedulingPriority = int; + isFcitxEngine = bool; + isIbusEngine = bool; + isGutenprint = bool; + badPlatforms = platforms; + }; + + checkMetaAttr = + k: v: + if metaTypes ? ${k} then + if typeCheck metaTypes.${k} v then + null + else + "key 'meta.${k}' has invalid value; expected ${metaTypes.${k}.description}, got\n ${ + lib.generators.toPretty { indent = " "; } v + }" + else + "key 'meta.${k}' is unrecognized; expected one of: \n [${ + lib.concatMapStringsSep ", " (x: "'${x}'") (lib.attrNames metaTypes) + }]"; + checkMeta = + meta: + lib.optionals config.checkMeta ( + lib.remove null (lib.mapAttrsToList checkMetaAttr meta) + ); + + checkOutputsToInstall = + attrs: + let + expectedOutputs = attrs.meta.outputsToInstall or [ ]; + actualOutputs = attrs.outputs or [ "out" ]; + missingOutputs = builtins.filter ( + output: !builtins.elem output actualOutputs + ) expectedOutputs; + in + if config.checkMeta then builtins.length missingOutputs > 0 else false; + + # Check if a derivation is valid, that is whether it passes checks for + # e.g brokenness or license. + # + # Return { valid: "yes", "warn" or "no" } and additionally + # { reason: String; errormsg: String } if it is not valid, where + # reason is one of "unfree", "blocklisted", "broken", "insecure", ... + # !!! reason strings are hardcoded into OfBorg, make sure to keep them in sync + # Along with a boolean flag for each reason + checkValidity = + attrs: + # Check meta attribute types first, to make sure it is always called even when there are other issues + # Note that this is not a full type check and functions below still need to by careful about their inputs! + let + res = checkMeta (attrs.meta or { }); + in + if res != [ ] then + { + valid = "no"; + reason = "unknown-meta"; + errormsg = "has an invalid meta attrset:${ + lib.concatMapStrings (x: "\n - " + x) res + }\n"; + unfree = false; + nonSource = false; + broken = false; + unsupported = false; + insecure = false; + } + else + { + unfree = hasUnfreeLicense attrs; + nonSource = hasNonSourceProvenance attrs; + broken = isMarkedBroken attrs; + unsupported = hasUnsupportedPlatform attrs; + insecure = isMarkedInsecure attrs; + } + // ( + # --- Put checks that cannot be ignored here --- + if checkOutputsToInstall attrs then + { + valid = "no"; + reason = "broken-outputs"; + errormsg = "has invalid meta.outputsToInstall"; + } + + # --- Put checks that can be ignored here --- + else if hasDeniedUnfreeLicense attrs && !(hasAllowlistedLicense attrs) then + { + valid = "no"; + reason = "unfree"; + errormsg = "has an unfree license (‘${showLicense attrs.meta.license}’)"; + } + else if hasBlocklistedLicense attrs then + { + valid = "no"; + reason = "blocklisted"; + errormsg = "has a blocklisted license (‘${showLicense attrs.meta.license}’)"; + } + else if hasDeniedNonSourceProvenance attrs then + { + valid = "no"; + reason = "non-source"; + errormsg = "contains elements not built from source (‘${showSourceType attrs.meta.sourceProvenance}’)"; + } + else if !allowBroken && attrs.meta.broken or false then + { + valid = "no"; + reason = "broken"; + errormsg = "is marked as broken"; + } + else if !allowUnsupportedSystem && hasUnsupportedPlatform attrs then + let + toPretty = lib.generators.toPretty { + allowPrettyValues = true; + indent = " "; + }; + in + { + valid = "no"; + reason = "unsupported"; + errormsg = '' + is not available on the requested hostPlatform: + hostPlatform.config = "${hostPlatform.config}" + package.meta.platforms = ${toPretty (attrs.meta.platforms or [ ])} + package.meta.badPlatforms = ${toPretty (attrs.meta.badPlatforms or [ ])} + ''; + } + else if !(hasAllowedInsecure attrs) then + { + valid = "no"; + reason = "insecure"; + errormsg = "is marked as insecure"; + } + + # --- warnings --- + # Please also update the type in /pkgs/top-level/config.nix alongside this. + else if hasNoMaintainers attrs then + { + valid = "warn"; + reason = "maintainerless"; + errormsg = "has no maintainers"; + } + # ----- + else + { valid = "yes"; } + ); + + # The meta attribute is passed in the resulting attribute set, + # but it's not part of the actual derivation, i.e., it's not + # passed to the builder and is not a dependency. But since we + # include it in the result, it *is* available to nix-env for queries. + # Example: + # meta = checkMeta.commonMeta { inherit validity attrs pos references; }; + # validity = checkMeta.assertValidity { inherit meta attrs; }; + commonMeta = + { + validity, + attrs, + pos ? null, + references ? [ ], + }: + let + outputs = attrs.outputs or [ "out" ]; + in + { + # `name` derivation attribute includes cross-compilation cruft, + # is under assert, and is sanitized. + # Let's have a clean always accessible version here. + name = attrs.name or "${attrs.pname}-${attrs.version}"; + + # If the packager hasn't specified `outputsToInstall`, choose a default, + # which is the name of `p.bin or p.out or p` along with `p.man` when + # present. + # + # If the packager has specified it, it will be overridden below in + # `// meta`. + # + # Note: This default probably shouldn't be globally configurable. + # Services and users should specify outputs explicitly, + # unless they are comfortable with this default. + outputsToInstall = + let + hasOutput = out: builtins.elem out outputs; + in + [ + (lib.findFirst hasOutput null ( + [ + "bin" + "out" + ] + ++ outputs + )) + ] + ++ lib.optional (hasOutput "man") "man"; + } + // attrs.meta or { } + # Fill `meta.position` to identify the source location of the package. + // lib.optionalAttrs (pos != null) { + position = pos.file + ":" + toString pos.line; + } + // { + # Expose the result of the checks for everyone to see. + inherit (validity) + unfree + broken + unsupported + insecure + ; + + available = + validity.valid != "no" + && ( + if config.checkMetaRecursively or false then + lib.all (d: d.meta.available or true) references + else + true + ); + }; + + assertValidity = + { meta, attrs }: + let + validity = checkValidity attrs; + in + validity + // { + # Throw an error if trying to evaluate a non-valid derivation + # or, alternatively, just output a warning message. + handled = + { + no = handleEvalIssue { inherit meta attrs; } { + inherit (validity) reason errormsg; + }; + warn = handleEvalWarning { inherit meta attrs; } { + inherit (validity) reason errormsg; + }; + yes = true; + } + .${validity.valid}; + + }; + +in +{ + inherit assertValidity commonMeta; +} diff --git a/test/diff/idioms_nixos_1/out-pure.nix b/test/diff/idioms_nixos_1/out-pure.nix new file mode 100644 index 00000000..f2bcf7ff --- /dev/null +++ b/test/diff/idioms_nixos_1/out-pure.nix @@ -0,0 +1,392 @@ +{ + config, + lib, + pkgs, + ... +}: + +with lib; + +let + + inherit (config.boot) kernelPatches; + inherit (config.boot.kernel) features randstructSeed; + inherit (config.boot.kernelPackages) kernel; + + kernelModulesConf = pkgs.writeText "nixos.conf" '' + ${concatStringsSep "\n" config.boot.kernelModules} + ''; + +in + +{ + + ###### interface + + options = { + + boot.kernel.features = mkOption { + default = { }; + example = literalExpression "{ debug = true; }"; + internal = true; + description = '' + This option allows to enable or disable certain kernel features. + It's not API, because it's about kernel feature sets, that + make sense for specific use cases. Mostly along with programs, + which would have separate nixos options. + `grep features pkgs/os-specific/linux/kernel/common-config.nix` + ''; + }; + + boot.kernelPackages = mkOption { + default = pkgs.linuxPackages; + type = types.unspecified // { + merge = mergeEqualOption; + }; + apply = + kernelPackages: + kernelPackages.extend ( + self: super: { + kernel = super.kernel.override (originalArgs: { + inherit randstructSeed; + kernelPatches = (originalArgs.kernelPatches or [ ]) ++ kernelPatches; + features = lib.recursiveUpdate super.kernel.features features; + }); + } + ); + # We don't want to evaluate all of linuxPackages for the manual + # - some of it might not even evaluate correctly. + defaultText = literalExpression "pkgs.linuxPackages"; + example = literalExpression "pkgs.linuxKernel.packages.linux_5_10"; + description = '' + This option allows you to override the Linux kernel used by + NixOS. Since things like external kernel module packages are + tied to the kernel you're using, it also overrides those. + This option is a function that takes Nixpkgs as an argument + (as a convenience), and returns an attribute set containing at + the very least an attribute kernel. + Additional attributes may be needed depending on your + configuration. For instance, if you use the NVIDIA X driver, + then it also needs to contain an attribute + nvidia_x11. + ''; + }; + + boot.kernelPatches = mkOption { + type = types.listOf types.attrs; + default = [ ]; + example = literalExpression "[ pkgs.kernelPatches.ubuntu_fan_4_4 ]"; + description = "A list of additional patches to apply to the kernel."; + }; + + boot.kernel.randstructSeed = mkOption { + type = types.str; + default = ""; + example = "my secret seed"; + description = '' + Provides a custom seed for the RANDSTRUCT security + option of the Linux kernel. Note that RANDSTRUCT is + only enabled in NixOS hardened kernels. Using a custom seed requires + building the kernel and dependent packages locally, since this + customization happens at build time. + ''; + }; + + boot.kernelParams = mkOption { + type = types.listOf ( + types.strMatching ''([^"[:space:]]|"[^"]*")+'' + // { + name = "kernelParam"; + description = "string, with spaces inside double quotes"; + } + ); + default = [ ]; + description = "Parameters added to the kernel command line."; + }; + + boot.consoleLogLevel = mkOption { + type = types.int; + default = 4; + description = '' + The kernel console loglevel. All Kernel Messages with a log level smaller + than this setting will be printed to the console. + ''; + }; + + boot.vesa = mkOption { + type = types.bool; + default = false; + description = '' + (Deprecated) This option, if set, activates the VESA 800x600 video + mode on boot and disables kernel modesetting. It is equivalent to + specifying [ "vga=0x317" "nomodeset" ] in the + option. This option is + deprecated as of 2020: Xorg now works better with modesetting, and + you might want a different VESA vga setting, anyway. + ''; + }; + + boot.extraModulePackages = mkOption { + type = types.listOf types.package; + default = [ ]; + example = literalExpression "[ config.boot.kernelPackages.nvidia_x11 ]"; + description = "A list of additional packages supplying kernel modules."; + }; + + boot.kernelModules = mkOption { + type = types.listOf types.str; + default = [ ]; + description = '' + The set of kernel modules to be loaded in the second stage of + the boot process. Note that modules that are needed to + mount the root file system should be added to + or + . + ''; + }; + + boot.initrd.availableKernelModules = mkOption { + type = types.listOf types.str; + default = [ ]; + example = [ + "sata_nv" + "ext3" + ]; + description = '' + The set of kernel modules in the initial ramdisk used during the + boot process. This set must include all modules necessary for + mounting the root device. That is, it should include modules + for the physical device (e.g., SCSI drivers) and for the file + system (e.g., ext3). The set specified here is automatically + closed under the module dependency relation, i.e., all + dependencies of the modules list here are included + automatically. The modules listed here are available in the + initrd, but are only loaded on demand (e.g., the ext3 module is + loaded automatically when an ext3 filesystem is mounted, and + modules for PCI devices are loaded when they match the PCI ID + of a device in your system). To force a module to be loaded, + include it in . + ''; + }; + + boot.initrd.kernelModules = mkOption { + type = types.listOf types.str; + default = [ ]; + description = "List of modules that are always loaded by the initrd."; + }; + + boot.initrd.includeDefaultModules = mkOption { + type = types.bool; + default = true; + description = '' + This option, if set, adds a collection of default kernel modules + to and + . + ''; + }; + + system.modulesTree = mkOption { + type = types.listOf types.path; + internal = true; + default = [ ]; + description = '' + Tree of kernel modules. This includes the kernel, plus modules + built outside of the kernel. Combine these into a single tree of + symlinks because modprobe only supports one directory. + ''; + # Convert the list of path to only one path. + apply = pkgs.aggregateModules; + }; + + system.requiredKernelConfig = mkOption { + default = [ ]; + example = literalExpression '' + with config.lib.kernelConfig; [ + (isYes "MODULES") + (isEnabled "FB_CON_DECOR") + (isEnabled "BLK_DEV_INITRD") + ] + ''; + internal = true; + type = types.listOf types.attrs; + description = '' + This option allows modules to specify the kernel config options that + must be set (or unset) for the module to work. Please use the + lib.kernelConfig functions to build list elements. + ''; + }; + + }; + + ###### implementation + + config = mkMerge [ + (mkIf config.boot.initrd.enable { + boot.initrd.availableKernelModules = + optionals config.boot.initrd.includeDefaultModules + ( + [ + # Note: most of these (especially the SATA/PATA modules) + # shouldn't be included by default since nixos-generate-config + # detects them, but I'm keeping them for now for backwards + # compatibility. + + # Some SATA/PATA stuff. + "ahci" + "sata_nv" + "sata_via" + "sata_sis" + "sata_uli" + "ata_piix" + "pata_marvell" + + # Standard SCSI stuff. + "sd_mod" + "sr_mod" + + # SD cards and internal eMMC drives. + "mmc_block" + + # Support USB keyboards, in case the boot fails and we only have + # a USB keyboard, or for LUKS passphrase prompt. + "uhci_hcd" + "ehci_hcd" + "ehci_pci" + "ohci_hcd" + "ohci_pci" + "xhci_hcd" + "xhci_pci" + "usbhid" + "hid_generic" + "hid_lenovo" + "hid_apple" + "hid_roccat" + "hid_logitech_hidpp" + "hid_logitech_dj" + "hid_microsoft" + + ] + ++ optionals pkgs.stdenv.hostPlatform.isx86 [ + # Misc. x86 keyboard stuff. + "pcips2" + "atkbd" + "i8042" + + # x86 RTC needed by the stage 2 init script. + "rtc_cmos" + ] + ); + + boot.initrd.kernelModules = optionals config.boot.initrd.includeDefaultModules [ + # For LVM. + "dm_mod" + ]; + }) + + (mkIf (!config.boot.isContainer) { + system.build = { + inherit kernel; + }; + + system.modulesTree = [ kernel ] ++ config.boot.extraModulePackages; + + # Implement consoleLogLevel both in early boot and using sysctl + # (so you don't need to reboot to have changes take effect). + boot.kernelParams = + [ "loglevel=${toString config.boot.consoleLogLevel}" ] + ++ optionals config.boot.vesa [ + "vga=0x317" + "nomodeset" + ]; + + boot.kernel.sysctl."kernel.printk" = mkDefault config.boot.consoleLogLevel; + + boot.kernelModules = [ + "loop" + "atkbd" + ]; + + # The Linux kernel >= 2.6.27 provides firmware. + hardware.firmware = [ kernel ]; + + # Create /etc/modules-load.d/nixos.conf, which is read by + # systemd-modules-load.service to load required kernel modules. + environment.etc = { + "modules-load.d/nixos.conf".source = kernelModulesConf; + }; + + systemd.services.systemd-modules-load = { + wantedBy = [ "multi-user.target" ]; + restartTriggers = [ kernelModulesConf ]; + serviceConfig = { + # Ignore failed module loads. Typically some of the + # modules in ‘boot.kernelModules’ are "nice to have but + # not required" (e.g. acpi-cpufreq), so we don't want to + # barf on those. + SuccessExitStatus = "0 1"; + }; + }; + + lib.kernelConfig = { + isYes = option: { + assertion = config: config.isYes option; + message = "CONFIG_${option} is not yes!"; + configLine = "CONFIG_${option}=y"; + }; + + isNo = option: { + assertion = config: config.isNo option; + message = "CONFIG_${option} is not no!"; + configLine = "CONFIG_${option}=n"; + }; + + isModule = option: { + assertion = config: config.isModule option; + message = "CONFIG_${option} is not built as a module!"; + configLine = "CONFIG_${option}=m"; + }; + + ### Usually you will just want to use these two + # True if yes or module + isEnabled = option: { + assertion = config: config.isEnabled option; + message = "CONFIG_${option} is not enabled!"; + configLine = "CONFIG_${option}=y"; + }; + + # True if no or omitted + isDisabled = option: { + assertion = config: config.isDisabled option; + message = "CONFIG_${option} is not disabled!"; + configLine = "CONFIG_${option}=n"; + }; + }; + + # The config options that all modules can depend upon + system.requiredKernelConfig = + with config.lib.kernelConfig; + [ + # !!! Should this really be needed? + (isYes "MODULES") + (isYes "BINFMT_ELF") + ] + ++ (optional (randstructSeed != "") (isYes "GCC_PLUGIN_RANDSTRUCT")); + + # nixpkgs kernels are assumed to have all required features + assertions = + if config.boot.kernelPackages.kernel ? features then + [ ] + else + let + cfg = config.boot.kernelPackages.kernel.config; + in + map (attrs: { + assertion = attrs.assertion cfg; + inherit (attrs) message; + }) config.system.requiredKernelConfig; + + }) + + ]; + +} diff --git a/test/diff/idioms_nixos_2/out-pure.nix b/test/diff/idioms_nixos_2/out-pure.nix new file mode 100644 index 00000000..e7d3e5d2 --- /dev/null +++ b/test/diff/idioms_nixos_2/out-pure.nix @@ -0,0 +1,1282 @@ +{ + config, + lib, + pkgs, + ... +}: + +with lib; + +let + cfg = config.services.nextcloud; + fpm = config.services.phpfpm.pools.nextcloud; + + jsonFormat = pkgs.formats.json { }; + + inherit (cfg) datadir; + + phpPackage = cfg.phpPackage.buildEnv { + extensions = + { enabled, all }: + ( + with all; + # disable default openssl extension + (lib.filter (e: e.pname != "php-openssl") enabled) + # use OpenSSL 1.1 for RC4 Nextcloud encryption if user + # has acknowledged the brokenness of the ciphers (RC4). + # TODO: remove when https://github.com/nextcloud/server/issues/32003 is fixed. + ++ ( + if cfg.enableBrokenCiphersForSSE then + [ cfg.phpPackage.extensions.openssl-legacy ] + else + [ cfg.phpPackage.extensions.openssl ] + ) + ++ optional cfg.enableImagemagick imagick + # Optionally enabled depending on caching settings + ++ optional cfg.caching.apcu apcu + ++ optional cfg.caching.redis redis + ++ optional cfg.caching.memcached memcached + ) + ++ cfg.phpExtraExtensions all; # Enabled by user + extraConfig = toKeyValue phpOptions; + }; + + toKeyValue = generators.toKeyValue { + mkKeyValue = generators.mkKeyValueDefault { } " = "; + }; + + phpOptions = + { + upload_max_filesize = cfg.maxUploadSize; + post_max_size = cfg.maxUploadSize; + memory_limit = cfg.maxUploadSize; + } + // cfg.phpOptions // optionalAttrs cfg.caching.apcu { "apc.enable_cli" = "1"; }; + + occ = pkgs.writeScriptBin "nextcloud-occ" '' + #! ${pkgs.runtimeShell} + cd ${cfg.package} + sudo=exec + if [[ "$USER" != nextcloud ]]; then + sudo='exec /run/wrappers/bin/sudo -u nextcloud --preserve-env=NEXTCLOUD_CONFIG_DIR --preserve-env=OC_PASS' + fi + export NEXTCLOUD_CONFIG_DIR="${datadir}/config" + $sudo \ + ${phpPackage}/bin/php \ + occ "$@" + ''; + + inherit (config.system) stateVersion; + +in +{ + + imports = [ + (mkRemovedOptionModule + [ + "services" + "nextcloud" + "config" + "adminpass" + ] + '' + Please use `services.nextcloud.config.adminpassFile' instead! + '' + ) + (mkRemovedOptionModule + [ + "services" + "nextcloud" + "config" + "dbpass" + ] + '' + Please use `services.nextcloud.config.dbpassFile' instead! + '' + ) + (mkRemovedOptionModule + [ + "services" + "nextcloud" + "nginx" + "enable" + ] + '' + The nextcloud module supports `nginx` as reverse-proxy by default and doesn't + support other reverse-proxies officially. + + However it's possible to use an alternative reverse-proxy by + + * disabling nginx + * setting `listen.owner` & `listen.group` in the phpfpm-pool to a different value + + Further details about this can be found in the `Nextcloud`-section of the NixOS-manual + (which can be opened e.g. by running `nixos-help`). + '' + ) + (mkRemovedOptionModule + [ + "services" + "nextcloud" + "disableImagemagick" + ] + '' + Use services.nextcloud.enableImagemagick instead. + '' + ) + ]; + + options.services.nextcloud = { + enable = mkEnableOption (lib.mdDoc "nextcloud"); + + enableBrokenCiphersForSSE = mkOption { + type = types.bool; + default = versionOlder stateVersion "22.11"; + defaultText = literalExpression "versionOlder system.stateVersion \"22.11\""; + description = lib.mdDoc '' + This option enables using the OpenSSL PHP extension linked against OpenSSL 1.1 + rather than latest OpenSSL (≥ 3), this is not recommended unless you need + it for server-side encryption (SSE). SSE uses the legacy RC4 cipher which is + considered broken for several years now. See also [RFC7465](https://datatracker.ietf.org/doc/html/rfc7465). + + This cipher has been disabled in OpenSSL ≥ 3 and requires + a specific legacy profile to re-enable it. + + If you deploy Nextcloud using OpenSSL ≥ 3 for PHP and have + server-side encryption configured, you will not be able to access + your files anymore. Enabling this option can restore access to your files. + Upon testing we didn't encounter any data corruption when turning + this on and off again, but this cannot be guaranteed for + each Nextcloud installation. + + It is `true` by default for systems with a [](#opt-system.stateVersion) below + `22.11` to make sure that existing installations won't break on update. On newer + NixOS systems you have to explicitly enable it on your own. + + Please note that this only provides additional value when using + external storage such as S3 since it's not an end-to-end encryption. + If this is not the case, + it is advised to [disable server-side encryption](https://docs.nextcloud.com/server/latest/admin_manual/configuration_files/encryption_configuration.html#disabling-encryption) and set this to `false`. + + In the future, Nextcloud may move to AES-256-GCM, by then, + this option will be removed. + ''; + }; + hostName = mkOption { + type = types.str; + description = lib.mdDoc "FQDN for the nextcloud instance."; + }; + home = mkOption { + type = types.str; + default = "/var/lib/nextcloud"; + description = lib.mdDoc "Storage path of nextcloud."; + }; + datadir = mkOption { + type = types.str; + default = config.services.nextcloud.home; + defaultText = literalExpression "config.services.nextcloud.home"; + description = lib.mdDoc '' + Data storage path of nextcloud. Will be [](#opt-services.nextcloud.home) by default. + This folder will be populated with a config.php and data folder which contains the state of the instance (excl the database)."; + ''; + example = "/mnt/nextcloud-file"; + }; + extraApps = mkOption { + type = types.attrsOf types.package; + default = { }; + description = lib.mdDoc '' + Extra apps to install. Should be an attrSet of appid to packages generated by fetchNextcloudApp. + The appid must be identical to the "id" value in the apps appinfo/info.xml. + Using this will disable the appstore to prevent Nextcloud from updating these apps (see [](#opt-services.nextcloud.appstoreEnable)). + ''; + example = literalExpression '' + { + maps = pkgs.fetchNextcloudApp { + name = "maps"; + sha256 = "007y80idqg6b6zk6kjxg4vgw0z8fsxs9lajnv49vv1zjy6jx2i1i"; + url = "https://github.com/nextcloud/maps/releases/download/v0.1.9/maps-0.1.9.tar.gz"; + version = "0.1.9"; + }; + phonetrack = pkgs.fetchNextcloudApp { + name = "phonetrack"; + sha256 = "0qf366vbahyl27p9mshfma1as4nvql6w75zy2zk5xwwbp343vsbc"; + url = "https://gitlab.com/eneiluj/phonetrack-oc/-/wikis/uploads/931aaaf8dca24bf31a7e169a83c17235/phonetrack-0.6.9.tar.gz"; + version = "0.6.9"; + }; + } + ''; + }; + extraAppsEnable = mkOption { + type = types.bool; + default = true; + description = lib.mdDoc '' + Automatically enable the apps in [](#opt-services.nextcloud.extraApps) every time nextcloud starts. + If set to false, apps need to be enabled in the Nextcloud user interface or with nextcloud-occ app:enable. + ''; + }; + appstoreEnable = mkOption { + type = types.nullOr types.bool; + default = null; + example = true; + description = lib.mdDoc '' + Allow the installation of apps and app updates from the store. + Enabled by default unless there are packages in [](#opt-services.nextcloud.extraApps). + Set to true to force enable the store even if [](#opt-services.nextcloud.extraApps) is used. + Set to false to disable the installation of apps from the global appstore. App management is always enabled regardless of this setting. + ''; + }; + logLevel = mkOption { + type = types.ints.between 0 4; + default = 2; + description = lib.mdDoc "Log level value between 0 (DEBUG) and 4 (FATAL)."; + }; + logType = mkOption { + type = types.enum [ + "errorlog" + "file" + "syslog" + "systemd" + ]; + default = "syslog"; + description = lib.mdDoc '' + Logging backend to use. + systemd requires the php-systemd package to be added to services.nextcloud.phpExtraExtensions. + See the [nextcloud documentation](https://docs.nextcloud.com/server/latest/admin_manual/configuration_server/logging_configuration.html) for details. + ''; + }; + https = mkOption { + type = types.bool; + default = false; + description = lib.mdDoc "Use https for generated links."; + }; + package = mkOption { + type = types.package; + description = lib.mdDoc "Which package to use for the Nextcloud instance."; + relatedPackages = [ + "nextcloud24" + "nextcloud25" + "nextcloud26" + ]; + }; + phpPackage = mkOption { + type = types.package; + relatedPackages = [ + "php80" + "php81" + ]; + defaultText = "pkgs.php"; + description = lib.mdDoc '' + PHP package to use for Nextcloud. + ''; + }; + + maxUploadSize = mkOption { + default = "512M"; + type = types.str; + description = lib.mdDoc '' + Defines the upload limit for files. This changes the relevant options + in php.ini and nginx if enabled. + ''; + }; + + skeletonDirectory = mkOption { + default = ""; + type = types.str; + description = lib.mdDoc '' + The directory where the skeleton files are located. These files will be + copied to the data directory of new users. Leave empty to not copy any + skeleton files. + ''; + }; + + webfinger = mkOption { + type = types.bool; + default = false; + description = lib.mdDoc '' + Enable this option if you plan on using the webfinger plugin. + The appropriate nginx rewrite rules will be added to your configuration. + ''; + }; + + phpExtraExtensions = mkOption { + type = with types; functionTo (listOf package); + default = all: [ ]; + defaultText = literalExpression "all: []"; + description = lib.mdDoc '' + Additional PHP extensions to use for nextcloud. + By default, only extensions necessary for a vanilla nextcloud installation are enabled, + but you may choose from the list of available extensions and add further ones. + This is sometimes necessary to be able to install a certain nextcloud app that has additional requirements. + ''; + example = literalExpression '' + all: [ all.pdlib all.bz2 ] + ''; + }; + + phpOptions = mkOption { + type = types.attrsOf types.str; + default = { + short_open_tag = "Off"; + expose_php = "Off"; + error_reporting = "E_ALL & ~E_DEPRECATED & ~E_STRICT"; + display_errors = "stderr"; + "opcache.enable_cli" = "1"; + "opcache.interned_strings_buffer" = "8"; + "opcache.max_accelerated_files" = "10000"; + "opcache.memory_consumption" = "128"; + "opcache.revalidate_freq" = "1"; + "opcache.fast_shutdown" = "1"; + "openssl.cafile" = "/etc/ssl/certs/ca-certificates.crt"; + catch_workers_output = "yes"; + }; + description = lib.mdDoc '' + Options for PHP's php.ini file for nextcloud. + ''; + }; + + poolSettings = mkOption { + type = + with types; + attrsOf (oneOf [ + str + int + bool + ]); + default = { + "pm" = "dynamic"; + "pm.max_children" = "32"; + "pm.start_servers" = "2"; + "pm.min_spare_servers" = "2"; + "pm.max_spare_servers" = "4"; + "pm.max_requests" = "500"; + }; + description = lib.mdDoc '' + Options for nextcloud's PHP pool. See the documentation on `php-fpm.conf` for details on configuration directives. + ''; + }; + + poolConfig = mkOption { + type = types.nullOr types.lines; + default = null; + description = lib.mdDoc '' + Options for nextcloud's PHP pool. See the documentation on `php-fpm.conf` for details on configuration directives. + ''; + }; + + fastcgiTimeout = mkOption { + type = types.int; + default = 120; + description = lib.mdDoc '' + FastCGI timeout for database connection in seconds. + ''; + }; + + database = { + + createLocally = mkOption { + type = types.bool; + default = false; + description = lib.mdDoc '' + Create the database and database user locally. Only available for + mysql database. + Note that this option will use the latest version of MariaDB which + is not officially supported by Nextcloud. As for now a workaround + is used to also support MariaDB version >= 10.6. + ''; + }; + + }; + + config = { + dbtype = mkOption { + type = types.enum [ + "sqlite" + "pgsql" + "mysql" + ]; + default = "sqlite"; + description = lib.mdDoc "Database type."; + }; + dbname = mkOption { + type = types.nullOr types.str; + default = "nextcloud"; + description = lib.mdDoc "Database name."; + }; + dbuser = mkOption { + type = types.nullOr types.str; + default = "nextcloud"; + description = lib.mdDoc "Database user."; + }; + dbpassFile = mkOption { + type = types.nullOr types.str; + default = null; + description = lib.mdDoc '' + The full path to a file that contains the database password. + ''; + }; + dbhost = mkOption { + type = types.nullOr types.str; + default = "localhost"; + description = lib.mdDoc '' + Database host. + + Note: for using Unix authentication with PostgreSQL, this should be + set to `/run/postgresql`. + ''; + }; + dbport = mkOption { + type = with types; nullOr (either int str); + default = null; + description = lib.mdDoc "Database port."; + }; + dbtableprefix = mkOption { + type = types.nullOr types.str; + default = null; + description = lib.mdDoc "Table prefix in Nextcloud database."; + }; + adminuser = mkOption { + type = types.str; + default = "root"; + description = lib.mdDoc "Admin username."; + }; + adminpassFile = mkOption { + type = types.str; + description = lib.mdDoc '' + The full path to a file that contains the admin's password. Must be + readable by user `nextcloud`. + ''; + }; + + extraTrustedDomains = mkOption { + type = types.listOf types.str; + default = [ ]; + description = lib.mdDoc '' + Trusted domains, from which the nextcloud installation will be + accessible. You don't need to add + `services.nextcloud.hostname` here. + ''; + }; + + trustedProxies = mkOption { + type = types.listOf types.str; + default = [ ]; + description = lib.mdDoc '' + Trusted proxies, to provide if the nextcloud installation is being + proxied to secure against e.g. spoofing. + ''; + }; + + overwriteProtocol = mkOption { + type = types.nullOr ( + types.enum [ + "http" + "https" + ] + ); + default = null; + example = "https"; + + description = lib.mdDoc '' + Force Nextcloud to always use HTTPS i.e. for link generation. Nextcloud + uses the currently used protocol by default, but when behind a reverse-proxy, + it may use `http` for everything although Nextcloud + may be served via HTTPS. + ''; + }; + + defaultPhoneRegion = mkOption { + default = null; + type = types.nullOr types.str; + example = "DE"; + description = lib.mdDoc '' + ::: {.warning} + This option exists since Nextcloud 21! If older versions are used, + this will throw an eval-error! + ::: + + [ISO 3611-1](https://www.iso.org/iso-3166-country-codes.html) + country codes for automatic phone-number detection without a country code. + + With e.g. `DE` set, the `+49` can be omitted for + phone-numbers. + ''; + }; + + objectstore = { + s3 = { + enable = mkEnableOption ( + lib.mdDoc '' + S3 object storage as primary storage. + + This mounts a bucket on an Amazon S3 object storage or compatible + implementation into the virtual filesystem. + + Further details about this feature can be found in the + [upstream documentation](https://docs.nextcloud.com/server/22/admin_manual/configuration_files/primary_storage.html). + '' + ); + bucket = mkOption { + type = types.str; + example = "nextcloud"; + description = lib.mdDoc '' + The name of the S3 bucket. + ''; + }; + autocreate = mkOption { + type = types.bool; + description = lib.mdDoc '' + Create the objectstore if it does not exist. + ''; + }; + key = mkOption { + type = types.str; + example = "EJ39ITYZEUH5BGWDRUFY"; + description = lib.mdDoc '' + The access key for the S3 bucket. + ''; + }; + secretFile = mkOption { + type = types.str; + example = "/var/nextcloud-objectstore-s3-secret"; + description = lib.mdDoc '' + The full path to a file that contains the access secret. Must be + readable by user `nextcloud`. + ''; + }; + hostname = mkOption { + type = types.nullOr types.str; + default = null; + example = "example.com"; + description = lib.mdDoc '' + Required for some non-Amazon implementations. + ''; + }; + port = mkOption { + type = types.nullOr types.port; + default = null; + description = lib.mdDoc '' + Required for some non-Amazon implementations. + ''; + }; + useSsl = mkOption { + type = types.bool; + default = true; + description = lib.mdDoc '' + Use SSL for objectstore access. + ''; + }; + region = mkOption { + type = types.nullOr types.str; + default = null; + example = "REGION"; + description = lib.mdDoc '' + Required for some non-Amazon implementations. + ''; + }; + usePathStyle = mkOption { + type = types.bool; + default = false; + description = lib.mdDoc '' + Required for some non-Amazon S3 implementations. + + Ordinarily, requests will be made with + `http://bucket.hostname.domain/`, but with path style + enabled requests are made with + `http://hostname.domain/bucket` instead. + ''; + }; + sseCKeyFile = mkOption { + type = types.nullOr types.path; + default = null; + example = "/var/nextcloud-objectstore-s3-sse-c-key"; + description = lib.mdDoc '' + If provided this is the full path to a file that contains the key + to enable [server-side encryption with customer-provided keys][1] + (SSE-C). + + The file must contain a random 32-byte key encoded as a base64 + string, e.g. generated with the command + + ``` + openssl rand 32 | base64 + ``` + + Must be readable by user `nextcloud`. + + [1]: https://docs.aws.amazon.com/AmazonS3/latest/userguide/ServerSideEncryptionCustomerKeys.html + ''; + }; + }; + }; + }; + + enableImagemagick = + mkEnableOption ( + lib.mdDoc '' + the ImageMagick module for PHP. + This is used by the theming app and for generating previews of certain images (e.g. SVG and HEIF). + You may want to disable it for increased security. In that case, previews will still be available + for some images (e.g. JPEG and PNG). + See . + '' + ) + // { + default = true; + }; + + caching = { + apcu = mkOption { + type = types.bool; + default = true; + description = lib.mdDoc '' + Whether to load the APCu module into PHP. + ''; + }; + redis = mkOption { + type = types.bool; + default = false; + description = lib.mdDoc '' + Whether to load the Redis module into PHP. + You still need to enable Redis in your config.php. + See https://docs.nextcloud.com/server/14/admin_manual/configuration_server/caching_configuration.html + ''; + }; + memcached = mkOption { + type = types.bool; + default = false; + description = lib.mdDoc '' + Whether to load the Memcached module into PHP. + You still need to enable Memcached in your config.php. + See https://docs.nextcloud.com/server/14/admin_manual/configuration_server/caching_configuration.html + ''; + }; + }; + autoUpdateApps = { + enable = mkOption { + type = types.bool; + default = false; + description = lib.mdDoc '' + Run regular auto update of all apps installed from the nextcloud app store. + ''; + }; + startAt = mkOption { + type = with types; either str (listOf str); + default = "05:00:00"; + example = "Sun 14:00:00"; + description = lib.mdDoc '' + When to run the update. See `systemd.services..startAt`. + ''; + }; + }; + occ = mkOption { + type = types.package; + default = occ; + defaultText = literalMD "generated script"; + internal = true; + description = lib.mdDoc '' + The nextcloud-occ program preconfigured to target this Nextcloud instance. + ''; + }; + globalProfiles = mkEnableOption (lib.mdDoc "global profiles") // { + description = lib.mdDoc '' + Makes user-profiles globally available under `nextcloud.tld/u/user.name`. + Even though it's enabled by default in Nextcloud, it must be explicitly enabled + here because it has the side-effect that personal information is even accessible to + unauthenticated users by default. + + By default, the following properties are set to “Show to everyone” + if this flag is enabled: + - About + - Full name + - Headline + - Organisation + - Profile picture + - Role + - Twitter + - Website + + Only has an effect in Nextcloud 23 and later. + ''; + }; + + extraOptions = mkOption { + type = jsonFormat.type; + default = { }; + description = lib.mdDoc '' + Extra options which should be appended to nextcloud's config.php file. + ''; + example = literalExpression '' + { + redis = { + host = "/run/redis/redis.sock"; + port = 0; + dbindex = 0; + password = "secret"; + timeout = 1.5; + }; + } ''; + }; + + secretFile = mkOption { + type = types.nullOr types.str; + default = null; + description = lib.mdDoc '' + Secret options which will be appended to nextcloud's config.php file (written as JSON, in the same + form as the [](#opt-services.nextcloud.extraOptions) option), for example + `{"redis":{"password":"secret"}}`. + ''; + }; + + nginx = { + recommendedHttpHeaders = mkOption { + type = types.bool; + default = true; + description = lib.mdDoc "Enable additional recommended HTTP response headers"; + }; + hstsMaxAge = mkOption { + type = types.ints.positive; + default = 15552000; + description = lib.mdDoc '' + Value for the `max-age` directive of the HTTP + `Strict-Transport-Security` header. + + See section 6.1.1 of IETF RFC 6797 for detailed information on this + directive and header. + ''; + }; + }; + }; + + config = mkIf cfg.enable (mkMerge [ + { + warnings = + let + latest = 26; + upgradeWarning = major: nixos: '' + A legacy Nextcloud install (from before NixOS ${nixos}) may be installed. + + After nextcloud${toString major} is installed successfully, you can safely upgrade + to ${toString (major + 1)}. The latest version available is nextcloud${toString latest}. + + Please note that Nextcloud doesn't support upgrades across multiple major versions + (i.e. an upgrade from 16 is possible to 17, but not 16 to 18). + + The package can be upgraded by explicitly declaring the service-option + `services.nextcloud.package`. + ''; + + in + (optional (cfg.poolConfig != null) '' + Using config.services.nextcloud.poolConfig is deprecated and will become unsupported in a future release. + Please migrate your configuration to config.services.nextcloud.poolSettings. + '') + ++ (optional (versionOlder cfg.package.version "23") ( + upgradeWarning 22 "22.05" + )) + ++ (optional (versionOlder cfg.package.version "24") ( + upgradeWarning 23 "22.05" + )) + ++ (optional (versionOlder cfg.package.version "25") ( + upgradeWarning 24 "22.11" + )) + ++ (optional (versionOlder cfg.package.version "26") ( + upgradeWarning 25 "23.05" + )) + ++ (optional cfg.enableBrokenCiphersForSSE '' + You're using PHP's openssl extension built against OpenSSL 1.1 for Nextcloud. + This is only necessary if you're using Nextcloud's server-side encryption. + Please keep in mind that it's using the broken RC4 cipher. + + If you don't use that feature, you can switch to OpenSSL 3 and get + rid of this warning by declaring + + services.nextcloud.enableBrokenCiphersForSSE = false; + + If you need to use server-side encryption you can ignore this warning. + Otherwise you'd have to disable server-side encryption first in order + to be able to safely disable this option and get rid of this warning. + See on how to achieve this. + + For more context, here is the implementing pull request: https://github.com/NixOS/nixpkgs/pull/198470 + ''); + + services.nextcloud.package = + with pkgs; + mkDefault ( + if pkgs ? nextcloud then + throw '' + The `pkgs.nextcloud`-attribute has been removed. If it's supposed to be the default + nextcloud defined in an overlay, please set `services.nextcloud.package` to + `pkgs.nextcloud`. + '' + else if versionOlder stateVersion "22.11" then + nextcloud24 + else if versionOlder stateVersion "23.05" then + nextcloud25 + else + nextcloud26 + ); + + services.nextcloud.phpPackage = + if versionOlder cfg.package.version "26" then pkgs.php81 else pkgs.php82; + } + + { + assertions = [ + { + assertion = cfg.database.createLocally -> cfg.config.dbtype == "mysql"; + message = ''services.nextcloud.config.dbtype must be set to mysql if services.nextcloud.database.createLocally is set to true.''; + } + ]; + } + + { + systemd.timers.nextcloud-cron = { + wantedBy = [ "timers.target" ]; + after = [ "nextcloud-setup.service" ]; + timerConfig.OnBootSec = "5m"; + timerConfig.OnUnitActiveSec = "5m"; + timerConfig.Unit = "nextcloud-cron.service"; + }; + + systemd.tmpfiles.rules = [ "d ${cfg.home} 0750 nextcloud nextcloud" ]; + + systemd.services = { + # When upgrading the Nextcloud package, Nextcloud can report errors such as + # "The files of the app [all apps in /var/lib/nextcloud/apps] were not replaced correctly" + # Restarting phpfpm on Nextcloud package update fixes these issues (but this is a workaround). + phpfpm-nextcloud.restartTriggers = [ cfg.package ]; + + nextcloud-setup = + let + c = cfg.config; + writePhpArray = + a: "[${concatMapStringsSep "," (val: ''"${toString val}"'') a}]"; + requiresReadSecretFunction = c.dbpassFile != null || c.objectstore.s3.enable; + objectstoreConfig = + let + s3 = c.objectstore.s3; + in + optionalString s3.enable '' + 'objectstore' => [ + 'class' => '\\OC\\Files\\ObjectStore\\S3', + 'arguments' => [ + 'bucket' => '${s3.bucket}', + 'autocreate' => ${boolToString s3.autocreate}, + 'key' => '${s3.key}', + 'secret' => nix_read_secret('${s3.secretFile}'), + ${optionalString (s3.hostname != null) "'hostname' => '${s3.hostname}',"} + ${optionalString (s3.port != null) "'port' => ${toString s3.port},"} + 'use_ssl' => ${boolToString s3.useSsl}, + ${optionalString (s3.region != null) "'region' => '${s3.region}',"} + 'use_path_style' => ${boolToString s3.usePathStyle}, + ${ + optionalString ( + s3.sseCKeyFile != null + ) "'sse_c_key' => nix_read_secret('${s3.sseCKeyFile}')," + } + ], + ] + ''; + + showAppStoreSetting = cfg.appstoreEnable != null || cfg.extraApps != { }; + renderedAppStoreSetting = + let + x = cfg.appstoreEnable; + in + if x == null then "false" else boolToString x; + + nextcloudGreaterOrEqualThan = req: versionAtLeast cfg.package.version req; + + overrideConfig = pkgs.writeText "nextcloud-config.php" '' + [ + ${ + optionalString (cfg.extraApps != { }) + "[ 'path' => '${cfg.home}/nix-apps', 'url' => '/nix-apps', 'writable' => false ]," + } + [ 'path' => '${cfg.home}/apps', 'url' => '/apps', 'writable' => false ], + [ 'path' => '${cfg.home}/store-apps', 'url' => '/store-apps', 'writable' => true ], + ], + ${optionalString (showAppStoreSetting) "'appstoreenabled' => ${renderedAppStoreSetting},"} + 'datadirectory' => '${datadir}/data', + 'skeletondirectory' => '${cfg.skeletonDirectory}', + ${optionalString cfg.caching.apcu "'memcache.local' => '\\OC\\Memcache\\APCu',"} + 'log_type' => '${cfg.logType}', + 'loglevel' => '${builtins.toString cfg.logLevel}', + ${ + optionalString ( + c.overwriteProtocol != null + ) "'overwriteprotocol' => '${c.overwriteProtocol}'," + } + ${optionalString (c.dbname != null) "'dbname' => '${c.dbname}',"} + ${optionalString (c.dbhost != null) "'dbhost' => '${c.dbhost}',"} + ${optionalString (c.dbport != null) "'dbport' => '${toString c.dbport}',"} + ${optionalString (c.dbuser != null) "'dbuser' => '${c.dbuser}',"} + ${ + optionalString ( + c.dbtableprefix != null + ) "'dbtableprefix' => '${toString c.dbtableprefix}'," + } + ${ + optionalString (c.dbpassFile != null) '' + 'dbpassword' => nix_read_secret( + "${c.dbpassFile}" + ), + '' + } + 'dbtype' => '${c.dbtype}', + 'trusted_domains' => ${ + writePhpArray ([ cfg.hostName ] ++ c.extraTrustedDomains) + }, + 'trusted_proxies' => ${writePhpArray (c.trustedProxies)}, + ${ + optionalString ( + c.defaultPhoneRegion != null + ) "'default_phone_region' => '${c.defaultPhoneRegion}'," + } + ${optionalString (nextcloudGreaterOrEqualThan "23") "'profile.enabled' => ${boolToString cfg.globalProfiles},"} + ${objectstoreConfig} + ]; + + $CONFIG = array_replace_recursive($CONFIG, nix_decode_json_file( + "${jsonFormat.generate "nextcloud-extraOptions.json" cfg.extraOptions}", + "impossible: this should never happen (decoding generated extraOptions file %s failed)" + )); + + ${optionalString (cfg.secretFile != null) '' + $CONFIG = array_replace_recursive($CONFIG, nix_decode_json_file( + "${cfg.secretFile}", + "Cannot start Nextcloud, secrets file %s set by NixOS doesn't exist!" + )); + ''} + ''; + occInstallCmd = + let + mkExport = { arg, value }: "export ${arg}=${value}"; + dbpass = { + arg = "DBPASS"; + value = + if c.dbpassFile != null then ''"$(<"${toString c.dbpassFile}")"'' else ''""''; + }; + adminpass = { + arg = "ADMINPASS"; + value = ''"$(<"${toString c.adminpassFile}")"''; + }; + installFlags = concatStringsSep " \\\n " ( + mapAttrsToList (k: v: "${k} ${toString v}") { + "--database" = ''"${c.dbtype}"''; + # The following attributes are optional depending on the type of + # database. Those that evaluate to null on the left hand side + # will be omitted. + ${if c.dbname != null then "--database-name" else null} = ''"${c.dbname}"''; + ${if c.dbhost != null then "--database-host" else null} = ''"${c.dbhost}"''; + ${ + if c.dbport != null then "--database-port" else null + } = ''"${toString c.dbport}"''; + ${if c.dbuser != null then "--database-user" else null} = ''"${c.dbuser}"''; + "--database-pass" = "\"\$${dbpass.arg}\""; + "--admin-user" = ''"${c.adminuser}"''; + "--admin-pass" = "\"\$${adminpass.arg}\""; + "--data-dir" = ''"${datadir}/data"''; + } + ); + in + '' + ${mkExport dbpass} + ${mkExport adminpass} + ${occ}/bin/nextcloud-occ maintenance:install \ + ${installFlags} + ''; + occSetTrustedDomainsCmd = concatStringsSep "\n" ( + imap0 (i: v: '' + ${occ}/bin/nextcloud-occ config:system:set trusted_domains \ + ${toString i} --value="${toString v}" + '') ([ cfg.hostName ] ++ cfg.config.extraTrustedDomains) + ); + + in + { + wantedBy = [ "multi-user.target" ]; + before = [ "phpfpm-nextcloud.service" ]; + path = [ occ ]; + script = '' + ${optionalString (c.dbpassFile != null) '' + if [ ! -r "${c.dbpassFile}" ]; then + echo "dbpassFile ${c.dbpassFile} is not readable by nextcloud:nextcloud! Aborting..." + exit 1 + fi + if [ -z "$(<${c.dbpassFile})" ]; then + echo "dbpassFile ${c.dbpassFile} is empty!" + exit 1 + fi + ''} + if [ ! -r "${c.adminpassFile}" ]; then + echo "adminpassFile ${c.adminpassFile} is not readable by nextcloud:nextcloud! Aborting..." + exit 1 + fi + if [ -z "$(<${c.adminpassFile})" ]; then + echo "adminpassFile ${c.adminpassFile} is empty!" + exit 1 + fi + + ln -sf ${cfg.package}/apps ${cfg.home}/ + + # Install extra apps + ln -sfT \ + ${ + pkgs.linkFarm "nix-apps" ( + mapAttrsToList (name: path: { inherit name path; }) cfg.extraApps + ) + } \ + ${cfg.home}/nix-apps + + # create nextcloud directories. + # if the directories exist already with wrong permissions, we fix that + for dir in ${datadir}/config ${datadir}/data ${cfg.home}/store-apps ${cfg.home}/nix-apps; do + if [ ! -e $dir ]; then + install -o nextcloud -g nextcloud -d $dir + elif [ $(stat -c "%G" $dir) != "nextcloud" ]; then + chgrp -R nextcloud $dir + fi + done + + ln -sf ${overrideConfig} ${datadir}/config/override.config.php + + # Do not install if already installed + if [[ ! -e ${datadir}/config/config.php ]]; then + ${occInstallCmd} + fi + + ${occ}/bin/nextcloud-occ upgrade + + ${occ}/bin/nextcloud-occ config:system:delete trusted_domains + + ${optionalString (cfg.extraAppsEnable && cfg.extraApps != { }) '' + # Try to enable apps + ${occ}/bin/nextcloud-occ app:enable ${concatStringsSep " " (attrNames cfg.extraApps)} + ''} + + ${occSetTrustedDomainsCmd} + ''; + serviceConfig.Type = "oneshot"; + serviceConfig.User = "nextcloud"; + # On Nextcloud ≥ 26, it is not necessary to patch the database files to prevent + # an automatic creation of the database user. + environment.NC_setup_create_db_user = lib.mkIf (nextcloudGreaterOrEqualThan "26") "false"; + }; + nextcloud-cron = { + after = [ "nextcloud-setup.service" ]; + environment.NEXTCLOUD_CONFIG_DIR = "${datadir}/config"; + serviceConfig.Type = "oneshot"; + serviceConfig.User = "nextcloud"; + serviceConfig.ExecStart = "${phpPackage}/bin/php -f ${cfg.package}/cron.php"; + }; + nextcloud-update-plugins = mkIf cfg.autoUpdateApps.enable { + after = [ "nextcloud-setup.service" ]; + serviceConfig.Type = "oneshot"; + serviceConfig.ExecStart = "${occ}/bin/nextcloud-occ app:update --all"; + serviceConfig.User = "nextcloud"; + startAt = cfg.autoUpdateApps.startAt; + }; + }; + + services.phpfpm = { + pools.nextcloud = { + user = "nextcloud"; + group = "nextcloud"; + phpPackage = phpPackage; + phpEnv = { + NEXTCLOUD_CONFIG_DIR = "${datadir}/config"; + PATH = "/run/wrappers/bin:/nix/var/nix/profiles/default/bin:/run/current-system/sw/bin:/usr/bin:/bin"; + }; + settings = + mapAttrs (name: mkDefault) { + "listen.owner" = config.services.nginx.user; + "listen.group" = config.services.nginx.group; + } + // cfg.poolSettings; + extraConfig = cfg.poolConfig; + }; + }; + + users.users.nextcloud = { + home = "${cfg.home}"; + group = "nextcloud"; + isSystemUser = true; + }; + users.groups.nextcloud.members = [ + "nextcloud" + config.services.nginx.user + ]; + + environment.systemPackages = [ occ ]; + + services.mysql = lib.mkIf cfg.database.createLocally { + enable = true; + package = lib.mkDefault pkgs.mariadb; + ensureDatabases = [ cfg.config.dbname ]; + ensureUsers = [ + { + name = cfg.config.dbuser; + ensurePermissions = { + "${cfg.config.dbname}.*" = "ALL PRIVILEGES"; + }; + } + ]; + initialScript = pkgs.writeText "mysql-init" '' + CREATE USER '${cfg.config.dbname}'@'localhost' IDENTIFIED BY '${builtins.readFile (cfg.config.dbpassFile)}'; + CREATE DATABASE IF NOT EXISTS ${cfg.config.dbname}; + GRANT SELECT, INSERT, UPDATE, DELETE, CREATE, DROP, INDEX, ALTER, + CREATE TEMPORARY TABLES ON ${cfg.config.dbname}.* TO '${cfg.config.dbuser}'@'localhost' + IDENTIFIED BY '${builtins.readFile (cfg.config.dbpassFile)}'; + FLUSH privileges; + ''; + }; + + services.nginx.enable = mkDefault true; + + services.nginx.virtualHosts.${cfg.hostName} = { + root = cfg.package; + locations = { + "= /robots.txt" = { + priority = 100; + extraConfig = '' + allow all; + access_log off; + ''; + }; + "= /" = { + priority = 100; + extraConfig = '' + if ( $http_user_agent ~ ^DavClnt ) { + return 302 /remote.php/webdav/$is_args$args; + } + ''; + }; + "/" = { + priority = 900; + extraConfig = "rewrite ^ /index.php;"; + }; + "~ ^/store-apps" = { + priority = 201; + extraConfig = "root ${cfg.home};"; + }; + "~ ^/nix-apps" = { + priority = 201; + extraConfig = "root ${cfg.home};"; + }; + "^~ /.well-known" = { + priority = 210; + extraConfig = '' + absolute_redirect off; + location = /.well-known/carddav { + return 301 /remote.php/dav; + } + location = /.well-known/caldav { + return 301 /remote.php/dav; + } + location ~ ^/\.well-known/(?!acme-challenge|pki-validation) { + return 301 /index.php$request_uri; + } + try_files $uri $uri/ =404; + ''; + }; + "~ ^/(?:build|tests|config|lib|3rdparty|templates|data)(?:$|/)".extraConfig = '' + return 404; + ''; + "~ ^/(?:\\.(?!well-known)|autotest|occ|issue|indie|db_|console)".extraConfig = '' + return 404; + ''; + "~ ^\\/(?:index|remote|public|cron|core\\/ajax\\/update|status|ocs\\/v[12]|updater\\/.+|oc[ms]-provider\\/.+|.+\\/richdocumentscode\\/proxy)\\.php(?:$|\\/)" = { + priority = 500; + extraConfig = '' + include ${config.services.nginx.package}/conf/fastcgi.conf; + fastcgi_split_path_info ^(.+?\.php)(\\/.*)$; + set $path_info $fastcgi_path_info; + try_files $fastcgi_script_name =404; + fastcgi_param PATH_INFO $path_info; + fastcgi_param SCRIPT_FILENAME $document_root$fastcgi_script_name; + fastcgi_param HTTPS ${if cfg.https then "on" else "off"}; + fastcgi_param modHeadersAvailable true; + fastcgi_param front_controller_active true; + fastcgi_pass unix:${fpm.socket}; + fastcgi_intercept_errors on; + fastcgi_request_buffering off; + fastcgi_read_timeout ${builtins.toString cfg.fastcgiTimeout}s; + ''; + }; + "~ \\.(?:css|js|woff2?|svg|gif|map)$".extraConfig = '' + try_files $uri /index.php$request_uri; + expires 6M; + access_log off; + ''; + "~ ^\\/(?:updater|ocs-provider|ocm-provider)(?:$|\\/)".extraConfig = '' + try_files $uri/ =404; + index index.php; + ''; + "~ \\.(?:png|html|ttf|ico|jpg|jpeg|bcmap|mp4|webm)$".extraConfig = '' + try_files $uri /index.php$request_uri; + access_log off; + ''; + }; + extraConfig = '' + index index.php index.html /index.php$request_uri; + ${optionalString (cfg.nginx.recommendedHttpHeaders) '' + add_header X-Content-Type-Options nosniff; + add_header X-XSS-Protection "1; mode=block"; + add_header X-Robots-Tag "noindex, nofollow"; + add_header X-Download-Options noopen; + add_header X-Permitted-Cross-Domain-Policies none; + add_header X-Frame-Options sameorigin; + add_header Referrer-Policy no-referrer; + ''} + ${optionalString (cfg.https) '' + add_header Strict-Transport-Security "max-age=${toString cfg.nginx.hstsMaxAge}; includeSubDomains" always; + ''} + client_max_body_size ${cfg.maxUploadSize}; + fastcgi_buffers 64 4K; + fastcgi_hide_header X-Powered-By; + gzip on; + gzip_vary on; + gzip_comp_level 4; + gzip_min_length 256; + gzip_proxied expired no-cache no-store private no_last_modified no_etag auth; + gzip_types application/atom+xml application/javascript application/json application/ld+json application/manifest+json application/rss+xml application/vnd.geo+json application/vnd.ms-fontobject application/x-font-ttf application/x-web-app-manifest+json application/xhtml+xml application/xml font/opentype image/bmp image/svg+xml image/x-icon text/cache-manifest text/css text/plain text/vcard text/vnd.rim.location.xloc text/vtt text/x-component text/x-cross-domain-policy; + + ${optionalString cfg.webfinger '' + rewrite ^/.well-known/host-meta /public.php?service=host-meta last; + rewrite ^/.well-known/host-meta.json /public.php?service=host-meta-json last; + ''} + ''; + }; + } + ]); + + meta.doc = ./nextcloud.md; +} diff --git a/test/diff/idioms_nixos_2/out.nix b/test/diff/idioms_nixos_2/out.nix index e7d3e5d2..7502b9f9 100644 --- a/test/diff/idioms_nixos_2/out.nix +++ b/test/diff/idioms_nixos_2/out.nix @@ -51,7 +51,10 @@ let post_max_size = cfg.maxUploadSize; memory_limit = cfg.maxUploadSize; } - // cfg.phpOptions // optionalAttrs cfg.caching.apcu { "apc.enable_cli" = "1"; }; + // cfg.phpOptions + // optionalAttrs cfg.caching.apcu { + "apc.enable_cli" = "1"; + }; occ = pkgs.writeScriptBin "nextcloud-occ" '' #! ${pkgs.runtimeShell} diff --git a/test/diff/idioms_pkgs_1/out-pure.nix b/test/diff/idioms_pkgs_1/out-pure.nix new file mode 100644 index 00000000..afdbed26 --- /dev/null +++ b/test/diff/idioms_pkgs_1/out-pure.nix @@ -0,0 +1,16 @@ +{ + stdenv, + lib, + fetchFrom, + ... +}: + +stdenv.mkDerivation rec { + pname = "test"; + version = "0.0"; + src = fetchFrom { url = "example/${version}"; }; + meta = with lib; { + maintainers = with maintainers; [ someone ]; + description = "something"; + }; +} diff --git a/test/diff/idioms_pkgs_1/out.nix b/test/diff/idioms_pkgs_1/out.nix index afdbed26..12c0e5c3 100644 --- a/test/diff/idioms_pkgs_1/out.nix +++ b/test/diff/idioms_pkgs_1/out.nix @@ -8,7 +8,9 @@ stdenv.mkDerivation rec { pname = "test"; version = "0.0"; - src = fetchFrom { url = "example/${version}"; }; + src = fetchFrom { + url = "example/${version}"; + }; meta = with lib; { maintainers = with maintainers; [ someone ]; description = "something"; diff --git a/test/diff/idioms_pkgs_2/out-pure.nix b/test/diff/idioms_pkgs_2/out-pure.nix new file mode 100644 index 00000000..84f50d54 --- /dev/null +++ b/test/diff/idioms_pkgs_2/out-pure.nix @@ -0,0 +1,43 @@ +{ + lib, + stdenv, + fetchurl, + nixos, + testVersion, + testEqualDerivation, + hello, +}: + +stdenv.mkDerivation rec { + pname = "hello"; + version = "2.12"; + + src = fetchurl { + url = "mirror://gnu/hello/${pname}-${version}.tar.gz"; + sha256 = "1ayhp9v4m4rdhjmnl2bq3cibrbqqkgjbl3s7yk2nhlh8vj3ay16g"; + }; + + doCheck = true; + + passthru.tests = { + version = testVersion { package = hello; }; + + invariant-under-noXlibs = + testEqualDerivation "hello must not be rebuilt when environment.noXlibs is set." + hello + (nixos { environment.noXlibs = true; }).pkgs.hello; + }; + + meta = with lib; { + description = "A program that produces a familiar, friendly greeting"; + longDescription = '' + GNU Hello is a program that prints "Hello, world!" when you run it. + It is fully customizable. + ''; + homepage = "https://www.gnu.org/software/hello/manual/"; + changelog = "https://git.savannah.gnu.org/cgit/hello.git/plain/NEWS?h=v${version}"; + license = licenses.gpl3Plus; + maintainers = [ maintainers.eelco ]; + platforms = platforms.all; + }; +} diff --git a/test/diff/idioms_pkgs_3/out-pure.nix b/test/diff/idioms_pkgs_3/out-pure.nix new file mode 100644 index 00000000..066bc56e --- /dev/null +++ b/test/diff/idioms_pkgs_3/out-pure.nix @@ -0,0 +1,599 @@ +{ + pname, + version, + meta, + updateScript ? null, + binaryName ? "firefox", + application ? "browser", + applicationName ? "Mozilla Firefox", + branding ? null, + src, + unpackPhase ? null, + extraPatches ? [ ], + extraPostPatch ? "", + extraNativeBuildInputs ? [ ], + extraConfigureFlags ? [ ], + extraBuildInputs ? [ ], + extraMakeFlags ? [ ], + extraPassthru ? { }, + tests ? [ ], +}: + +{ + lib, + pkgs, + stdenv, + fetchpatch, + patchelf, + + # build time + autoconf, + cargo, + dump_syms, + makeWrapper, + nodejs, + perl, + pkg-config, + pkgsCross, # wasm32 rlbox + python3, + runCommand, + rustc, + rust-cbindgen, + rustPlatform, + unzip, + which, + wrapGAppsHook, + + # runtime + bzip2, + dbus, + dbus-glib, + file, + fontconfig, + freetype, + glib, + gnum4, + gtk3, + icu, + libGL, + libGLU, + libevent, + libffi, + libjpeg, + libpng, + libstartup_notification, + libvpx, + libwebp, + nasm, + nspr, + nss_esr, + nss_latest, + pango, + xorg, + zip, + zlib, + pkgsBuildBuild, + + # optionals + + ## debugging + + debugBuild ? false, + + # On 32bit platforms, we disable adding "-g" for easier linking. + enableDebugSymbols ? !stdenv.is32bit, + + ## optional libraries + + alsaSupport ? stdenv.isLinux, + alsa-lib, + ffmpegSupport ? true, + gssSupport ? true, + libkrb5, + jackSupport ? stdenv.isLinux, + libjack2, + jemallocSupport ? true, + jemalloc, + ltoSupport ? (stdenv.isLinux && stdenv.is64bit), + overrideCC, + buildPackages, + pgoSupport ? (stdenv.isLinux && stdenv.hostPlatform == stdenv.buildPlatform), + xvfb-run, + pipewireSupport ? waylandSupport && webrtcSupport, + pulseaudioSupport ? stdenv.isLinux, + libpulseaudio, + sndioSupport ? stdenv.isLinux, + sndio, + waylandSupport ? true, + libxkbcommon, + libdrm, + + ## privacy-related options + + privacySupport ? false, + + # WARNING: NEVER set any of the options below to `true` by default. + # Set to `!privacySupport` or `false`. + + crashreporterSupport ? !privacySupport, + curl, + geolocationSupport ? !privacySupport, + googleAPISupport ? geolocationSupport, + mlsAPISupport ? geolocationSupport, + webrtcSupport ? !privacySupport, + + # digital rights managemewnt + + # This flag controls whether Firefox will show the nagbar, that allows + # users at runtime the choice to enable Widevine CDM support when a site + # requests it. + # Controlling the nagbar and widevine CDM at runtime is possible by setting + # `browser.eme.ui.enabled` and `media.gmp-widevinecdm.enabled` accordingly + drmSupport ? true, + + # As stated by Sylvestre Ledru (@sylvestre) on Nov 22, 2017 at + # https://github.com/NixOS/nixpkgs/issues/31843#issuecomment-346372756 we + # have permission to use the official firefox branding. + # + # For purposes of documentation the statement of @sylvestre: + # > As the person who did part of the work described in the LWN article + # > and release manager working for Mozilla, I can confirm the statement + # > that I made in + # > https://bugs.debian.org/cgi-bin/bugreport.cgi?bug=815006 + # > + # > @garbas shared with me the list of patches applied for the Nix package. + # > As they are just for portability and tiny modifications, they don't + # > alter the experience of the product. In parallel, Rok also shared the + # > build options. They seem good (even if I cannot judge the quality of the + # > packaging of the underlying dependencies like sqlite, png, etc). + # > Therefor, as long as you keep the patch queue sane and you don't alter + # > the experience of Firefox users, you won't have any issues using the + # > official branding. + enableOfficialBranding ? true, +}: + +assert stdenv.cc.libc or null != null; +assert + pipewireSupport + -> !waylandSupport || !webrtcSupport + -> throw "${pname}: pipewireSupport requires both wayland and webrtc support."; + +let + inherit (lib) enableFeature; + + # Target the LLVM version that rustc is built with for LTO. + llvmPackages0 = rustc.llvmPackages; + llvmPackagesBuildBuild0 = pkgsBuildBuild.rustc.llvmPackages; + + # Force the use of lld and other llvm tools for LTO + llvmPackages = llvmPackages0.override { + bootBintoolsNoLibc = null; + bootBintools = null; + }; + llvmPackagesBuildBuild = llvmPackagesBuildBuild0.override { + bootBintoolsNoLibc = null; + bootBintools = null; + }; + + # LTO requires LLVM bintools including ld.lld and llvm-ar. + buildStdenv = overrideCC llvmPackages.stdenv ( + llvmPackages.stdenv.cc.override { + bintools = + if ltoSupport then + buildPackages.rustc.llvmPackages.bintools + else + stdenv.cc.bintools; + } + ); + + # Compile the wasm32 sysroot to build the RLBox Sandbox + # https://hacks.mozilla.org/2021/12/webassembly-and-back-again-fine-grained-sandboxing-in-firefox-95/ + # We only link c++ libs here, our compiler wrapper can find wasi libc and crt itself. + wasiSysRoot = runCommand "wasi-sysroot" { } '' + mkdir -p $out/lib/wasm32-wasi + for lib in ${pkgsCross.wasi32.llvmPackages.libcxx}/lib/* ${pkgsCross.wasi32.llvmPackages.libcxxabi}/lib/*; do + ln -s $lib $out/lib/wasm32-wasi + done + ''; + + distributionIni = pkgs.writeText "distribution.ini" ( + lib.generators.toINI { } { + # Some light branding indicating this build uses our distro preferences + Global = { + id = "nixos"; + version = "1.0"; + about = "${applicationName} for NixOS"; + }; + Preferences = { + # These values are exposed through telemetry + "app.distributor" = "nixos"; + "app.distributor.channel" = "nixpkgs"; + "app.partner.nixos" = "nixos"; + }; + } + ); + + defaultPrefs = { + "geo.provider.network.url" = { + value = "https://location.services.mozilla.com/v1/geolocate?key=%MOZILLA_API_KEY%"; + reason = "Use MLS by default for geolocation, since our Google API Keys are not working"; + }; + }; + + defaultPrefsFile = pkgs.writeText "nixos-default-prefs.js" ( + lib.concatStringsSep "\n" ( + lib.mapAttrsToList (key: value: '' + // ${value.reason} + pref("${key}", ${builtins.toJSON value.value}); + '') defaultPrefs + ) + ); + +in + +buildStdenv.mkDerivation ({ + pname = "${pname}-unwrapped"; + inherit version; + + inherit src unpackPhase meta; + + outputs = [ "out" ] ++ lib.optionals crashreporterSupport [ "symbols" ]; + + # Add another configure-build-profiling run before the final configure phase if we build with pgo + preConfigurePhases = lib.optionals pgoSupport [ + "configurePhase" + "buildPhase" + "profilingPhase" + ]; + + patches = + lib.optionals (lib.versionOlder version "102.6.0") [ + (fetchpatch { + # https://bugzilla.mozilla.org/show_bug.cgi?id=1773259 + name = "rust-cbindgen-0.24.2-compat.patch"; + url = "https://raw.githubusercontent.com/canonical/firefox-snap/5622734942524846fb0eb7108918c8cd8557fde3/patches/fix-ftbfs-newer-cbindgen.patch"; + hash = "sha256-+wNZhkDB3HSknPRD4N6cQXY7zMT/DzNXx29jQH0Gb1o="; + }) + ] + ++ lib.optional (lib.versionOlder version "111") ./env_var_for_system_dir-ff86.patch + ++ lib.optional (lib.versionAtLeast version "111") ./env_var_for_system_dir-ff111.patch + ++ lib.optional (lib.versionAtLeast version "96") ./no-buildconfig-ffx96.patch + ++ extraPatches; + + postPatch = + '' + rm -rf obj-x86_64-pc-linux-gnu + patchShebangs mach build + '' + + extraPostPatch; + + # Ignore trivial whitespace changes in patches, this fixes compatibility of + # ./env_var_for_system_dir.patch with Firefox >=65 without having to track + # two patches. + patchFlags = [ + "-p1" + "-l" + ]; + + # if not explicitly set, wrong cc from buildStdenv would be used + HOST_CC = "${llvmPackagesBuildBuild.stdenv.cc}/bin/cc"; + HOST_CXX = "${llvmPackagesBuildBuild.stdenv.cc}/bin/c++"; + + nativeBuildInputs = + [ + autoconf + cargo + gnum4 + llvmPackagesBuildBuild.bintools + makeWrapper + nodejs + perl + pkg-config + python3 + rust-cbindgen + rustPlatform.bindgenHook + rustc + unzip + which + wrapGAppsHook + ] + ++ lib.optionals crashreporterSupport [ + dump_syms + patchelf + ] + ++ lib.optionals pgoSupport [ xvfb-run ] + ++ extraNativeBuildInputs; + + setOutputFlags = false; # `./mach configure` doesn't understand `--*dir=` flags. + + preConfigure = + '' + # remove distributed configuration files + rm -f configure js/src/configure .mozconfig* + + # Runs autoconf through ./mach configure in configurePhase + configureScript="$(realpath ./mach) configure" + + # Set predictable directories for build and state + export MOZ_OBJDIR=$(pwd)/mozobj + export MOZBUILD_STATE_PATH=$(pwd)/mozbuild + + # Don't try to send libnotify notifications during build + export MOZ_NOSPAM=1 + + # Set consistent remoting name to ensure wmclass matches with desktop file + export MOZ_APP_REMOTINGNAME="${binaryName}" + + # AS=as in the environment causes build failure + # https://bugzilla.mozilla.org/show_bug.cgi?id=1497286 + unset AS + + # Use our own python + export MACH_BUILD_PYTHON_NATIVE_PACKAGE_SOURCE=system + + # RBox WASM Sandboxing + export WASM_CC=${pkgsCross.wasi32.stdenv.cc}/bin/${pkgsCross.wasi32.stdenv.cc.targetPrefix}cc + export WASM_CXX=${pkgsCross.wasi32.stdenv.cc}/bin/${pkgsCross.wasi32.stdenv.cc.targetPrefix}c++ + '' + + lib.optionalString pgoSupport '' + if [ -e "$TMPDIR/merged.profdata" ]; then + echo "Configuring with profiling data" + for i in "''${!configureFlagsArray[@]}"; do + if [[ ''${configureFlagsArray[i]} = "--enable-profile-generate=cross" ]]; then + unset 'configureFlagsArray[i]' + fi + done + configureFlagsArray+=( + "--enable-profile-use=cross" + "--with-pgo-profile-path="$TMPDIR/merged.profdata"" + "--with-pgo-jarlog="$TMPDIR/jarlog"" + ) + else + echo "Configuring to generate profiling data" + configureFlagsArray+=( + "--enable-profile-generate=cross" + ) + fi + '' + + lib.optionalString googleAPISupport '' + # Google API key used by Chromium and Firefox. + # Note: These are for NixOS/nixpkgs use ONLY. For your own distribution, + # please get your own set of keys at https://www.chromium.org/developers/how-tos/api-keys/. + echo "AIzaSyDGi15Zwl11UNe6Y-5XW_upsfyw31qwZPI" > $TMPDIR/google-api-key + # 60.5+ & 66+ did split the google API key arguments: https://bugzilla.mozilla.org/show_bug.cgi?id=1531176 + configureFlagsArray+=("--with-google-location-service-api-keyfile=$TMPDIR/google-api-key") + configureFlagsArray+=("--with-google-safebrowsing-api-keyfile=$TMPDIR/google-api-key") + '' + + lib.optionalString mlsAPISupport '' + # Mozilla Location services API key + # Note: These are for NixOS/nixpkgs use ONLY. For your own distribution, + # please get your own set of keys at https://location.services.mozilla.com/api. + echo "dfd7836c-d458-4917-98bb-421c82d3c8a0" > $TMPDIR/mls-api-key + configureFlagsArray+=("--with-mozilla-api-keyfile=$TMPDIR/mls-api-key") + '' + + lib.optionalString (enableOfficialBranding && !stdenv.is32bit) '' + export MOZILLA_OFFICIAL=1 + ''; + + # firefox has a different definition of configurePlatforms from nixpkgs, see configureFlags + configurePlatforms = [ ]; + + configureFlags = + [ + "--disable-tests" + "--disable-updater" + "--enable-application=${application}" + "--enable-default-toolkit=cairo-gtk3${lib.optionalString waylandSupport "-wayland"}" + "--enable-system-pixman" + "--with-distribution-id=org.nixos" + "--with-libclang-path=${llvmPackagesBuildBuild.libclang.lib}/lib" + "--with-system-ffi" + "--with-system-icu" + "--with-system-jpeg" + "--with-system-libevent" + "--with-system-libvpx" + "--with-system-nspr" + "--with-system-nss" + "--with-system-png" # needs APNG support + "--with-system-webp" + "--with-system-zlib" + "--with-wasi-sysroot=${wasiSysRoot}" + # for firefox, host is buildPlatform, target is hostPlatform + "--host=${buildStdenv.buildPlatform.config}" + "--target=${buildStdenv.hostPlatform.config}" + ] + # LTO is done using clang and lld on Linux. + ++ lib.optionals ltoSupport [ + "--enable-lto=cross" # Cross-Language LTO + "--enable-linker=lld" + ] + # elf-hack is broken when using clang+lld: + # https://bugzilla.mozilla.org/show_bug.cgi?id=1482204 + ++ lib.optional ( + ltoSupport + && (buildStdenv.isAarch32 || buildStdenv.isi686 || buildStdenv.isx86_64) + ) "--disable-elf-hack" + ++ lib.optional (!drmSupport) "--disable-eme" + ++ [ + (enableFeature alsaSupport "alsa") + (enableFeature crashreporterSupport "crashreporter") + (enableFeature ffmpegSupport "ffmpeg") + (enableFeature geolocationSupport "necko-wifi") + (enableFeature gssSupport "negotiateauth") + (enableFeature jackSupport "jack") + (enableFeature jemallocSupport "jemalloc") + (enableFeature pulseaudioSupport "pulseaudio") + (enableFeature sndioSupport "sndio") + (enableFeature webrtcSupport "webrtc") + (enableFeature debugBuild "debug") + (if debugBuild then "--enable-profiling" else "--enable-optimize") + # --enable-release adds -ffunction-sections & LTO that require a big amount + # of RAM, and the 32-bit memory space cannot handle that linking + (enableFeature (!debugBuild && !stdenv.is32bit) "release") + (enableFeature enableDebugSymbols "debug-symbols") + ] + ++ lib.optionals enableDebugSymbols [ + "--disable-strip" + "--disable-install-strip" + ] + ++ lib.optional enableOfficialBranding "--enable-official-branding" + ++ lib.optional (branding != null) "--with-branding=${branding}" + ++ extraConfigureFlags; + + buildInputs = + [ + bzip2 + dbus + dbus-glib + file + fontconfig + freetype + glib + gtk3 + icu + libffi + libGL + libGLU + libevent + libjpeg + libpng + libstartup_notification + libvpx + libwebp + nasm + nspr + pango + perl + xorg.libX11 + xorg.libXcursor + xorg.libXdamage + xorg.libXext + xorg.libXft + xorg.libXi + xorg.libXrender + xorg.libXt + xorg.libXtst + xorg.pixman + xorg.xorgproto + zip + zlib + ] + ++ [ (if (lib.versionAtLeast version "103") then nss_latest else nss_esr) ] + ++ lib.optional alsaSupport alsa-lib + ++ lib.optional jackSupport libjack2 + ++ lib.optional pulseaudioSupport libpulseaudio # only headers are needed + ++ lib.optional sndioSupport sndio + ++ lib.optional gssSupport libkrb5 + ++ lib.optionals waylandSupport [ + libxkbcommon + libdrm + ] + ++ lib.optional jemallocSupport jemalloc + ++ extraBuildInputs; + + profilingPhase = lib.optionalString pgoSupport '' + # Package up Firefox for profiling + ./mach package + + # Run profiling + ( + export HOME=$TMPDIR + export LLVM_PROFDATA=llvm-profdata + export JARLOG_FILE="$TMPDIR/jarlog" + + xvfb-run -w 10 -s "-screen 0 1920x1080x24" \ + ./mach python ./build/pgo/profileserver.py + ) + + # Copy profiling data to a place we can easily reference + cp ./merged.profdata $TMPDIR/merged.profdata + + # Clean build dir + ./mach clobber + ''; + + preBuild = '' + cd mozobj + ''; + + postBuild = '' + cd .. + ''; + + makeFlags = extraMakeFlags; + separateDebugInfo = enableDebugSymbols; + enableParallelBuilding = true; + + # tests were disabled in configureFlags + doCheck = false; + + # Generate build symbols once after the final build + # https://firefox-source-docs.mozilla.org/crash-reporting/uploading_symbol.html + preInstall = + lib.optionalString crashreporterSupport '' + ./mach buildsymbols + mkdir -p $symbols/ + cp mozobj/dist/*.crashreporter-symbols.zip $symbols/ + '' + + '' + cd mozobj + ''; + + postInstall = + '' + # Install distribution customizations + install -Dvm644 ${distributionIni} $out/lib/${binaryName}/distribution/distribution.ini + install -Dvm644 ${defaultPrefsFile} $out/lib/${binaryName}/browser/defaults/preferences/nixos-default-prefs.js + + '' + + lib.optionalString buildStdenv.isLinux '' + # Remove SDK cruft. FIXME: move to a separate output? + rm -rf $out/share/idl $out/include $out/lib/${binaryName}-devel-* + + # Needed to find Mozilla runtime + gappsWrapperArgs+=(--argv0 "$out/bin/.${binaryName}-wrapped") + ''; + + postFixup = lib.optionalString crashreporterSupport '' + patchelf --add-rpath "${lib.makeLibraryPath [ curl ]}" $out/lib/${binaryName}/crashreporter + ''; + + doInstallCheck = true; + installCheckPhase = '' + # Some basic testing + "$out/bin/${binaryName}" --version + ''; + + passthru = { + inherit updateScript; + inherit version; + inherit alsaSupport; + inherit binaryName; + inherit jackSupport; + inherit pipewireSupport; + inherit sndioSupport; + inherit nspr; + inherit ffmpegSupport; + inherit gssSupport; + inherit tests; + inherit gtk3; + inherit wasiSysRoot; + } // extraPassthru; + + hardeningDisable = [ "format" ]; # -Werror=format-security + + # the build system verifies checksums of the bundled rust sources + # ./third_party/rust is be patched by our libtool fixup code in stdenv + # unfortunately we can't just set this to `false` when we do not want it. + # See https://github.com/NixOS/nixpkgs/issues/77289 for more details + # Ideally we would figure out how to tell the build system to not + # care about changed hashes as we are already doing that when we + # fetch the sources. Any further modifications of the source tree + # is on purpose by some of our tool (or by accident and a bug?). + dontFixLibtool = true; + + # on aarch64 this is also required + dontUpdateAutotoolsGnuConfigScripts = true; + + requiredSystemFeatures = [ "big-parallel" ]; +}) diff --git a/test/diff/idioms_pkgs_3/out.nix b/test/diff/idioms_pkgs_3/out.nix index 066bc56e..13f30559 100644 --- a/test/diff/idioms_pkgs_3/out.nix +++ b/test/diff/idioms_pkgs_3/out.nix @@ -237,7 +237,9 @@ buildStdenv.mkDerivation ({ inherit src unpackPhase meta; - outputs = [ "out" ] ++ lib.optionals crashreporterSupport [ "symbols" ]; + outputs = [ + "out" + ] ++ lib.optionals crashreporterSupport [ "symbols" ]; # Add another configure-build-profiling run before the final configure phase if we build with pgo preConfigurePhases = lib.optionals pgoSupport [ diff --git a/test/diff/idioms_pkgs_4/out-pure.nix b/test/diff/idioms_pkgs_4/out-pure.nix new file mode 100644 index 00000000..a4ed06e4 --- /dev/null +++ b/test/diff/idioms_pkgs_4/out-pure.nix @@ -0,0 +1,218 @@ +{ + lib, + localSystem, + crossSystem, + config, + overlays, + crossOverlays ? [ ], +}: + +assert crossSystem == localSystem; + +let + inherit (localSystem) system; + + shell = + if system == "i686-freebsd" || system == "x86_64-freebsd" then + "/usr/local/bin/bash" + else + "/bin/bash"; + + path = + (lib.optionals (system == "i686-solaris") [ "/usr/gnu" ]) + ++ (lib.optionals (system == "i686-netbsd") [ "/usr/pkg" ]) + ++ (lib.optionals (system == "x86_64-solaris") [ "/opt/local/gnu" ]) + ++ [ + "/" + "/usr" + "/usr/local" + ]; + + prehookBase = '' + # Disable purity tests; it's allowed (even needed) to link to + # libraries outside the Nix store (like the C library). + export NIX_ENFORCE_PURITY= + export NIX_ENFORCE_NO_NATIVE="''${NIX_ENFORCE_NO_NATIVE-1}" + ''; + + prehookFreeBSD = '' + ${prehookBase} + + alias make=gmake + alias tar=gtar + alias sed=gsed + export MAKE=gmake + shopt -s expand_aliases + ''; + + prehookOpenBSD = '' + ${prehookBase} + + alias make=gmake + alias grep=ggrep + alias mv=gmv + alias ln=gln + alias sed=gsed + alias tar=gtar + + export MAKE=gmake + shopt -s expand_aliases + ''; + + prehookNetBSD = '' + ${prehookBase} + + alias make=gmake + alias sed=gsed + alias tar=gtar + export MAKE=gmake + shopt -s expand_aliases + ''; + + # prevent libtool from failing to find dynamic libraries + prehookCygwin = '' + ${prehookBase} + + shopt -s expand_aliases + export lt_cv_deplibs_check_method=pass_all + ''; + + extraNativeBuildInputsCygwin = + [ + ../cygwin/all-buildinputs-as-runtimedep.sh + ../cygwin/wrap-exes-to-find-dlls.sh + ] + ++ ( + if system == "i686-cygwin" then + [ ../cygwin/rebase-i686.sh ] + else if system == "x86_64-cygwin" then + [ ../cygwin/rebase-x86_64.sh ] + else + [ ] + ); + + # A function that builds a "native" stdenv (one that uses tools in + # /usr etc.). + makeStdenv = + { + cc, + fetchurl, + extraPath ? [ ], + overrides ? (self: super: { }), + extraNativeBuildInputs ? [ ], + }: + + import ../generic { + buildPlatform = localSystem; + hostPlatform = localSystem; + targetPlatform = localSystem; + + preHook = + if system == "i686-freebsd" then + prehookFreeBSD + else if system == "x86_64-freebsd" then + prehookFreeBSD + else if system == "i686-openbsd" then + prehookOpenBSD + else if system == "i686-netbsd" then + prehookNetBSD + else if system == "i686-cygwin" then + prehookCygwin + else if system == "x86_64-cygwin" then + prehookCygwin + else + prehookBase; + + extraNativeBuildInputs = + extraNativeBuildInputs + ++ ( + if system == "i686-cygwin" then + extraNativeBuildInputsCygwin + else if system == "x86_64-cygwin" then + extraNativeBuildInputsCygwin + else + [ ] + ); + + initialPath = extraPath ++ path; + + fetchurlBoot = fetchurl; + + inherit + shell + cc + overrides + config + ; + }; + +in + +[ + + ( + { }: + rec { + __raw = true; + + stdenv = makeStdenv { + cc = null; + fetchurl = null; + }; + stdenvNoCC = stdenv; + + cc = + let + nativePrefix = + { + # switch + i686-solaris = "/usr/gnu"; + x86_64-solaris = "/opt/local/gcc47"; + } + .${system} or "/usr"; + in + import ../../build-support/cc-wrapper { + name = "cc-native"; + nativeTools = true; + nativeLibc = true; + inherit lib nativePrefix; + bintools = import ../../build-support/bintools-wrapper { + name = "bintools"; + inherit lib stdenvNoCC nativePrefix; + nativeTools = true; + nativeLibc = true; + }; + inherit stdenvNoCC; + }; + + fetchurl = import ../../build-support/fetchurl { + inherit lib stdenvNoCC; + # Curl should be in /usr/bin or so. + curl = null; + }; + + } + ) + + # First build a stdenv based only on tools outside the store. + (prevStage: { + inherit config overlays; + stdenv = makeStdenv { inherit (prevStage) cc fetchurl; } // { + inherit (prevStage) fetchurl; + }; + }) + + # Using that, build a stdenv that adds the ‘xz’ command (which most systems + # don't have, so we mustn't rely on the native environment providing it). + (prevStage: { + inherit config overlays; + stdenv = makeStdenv { + inherit (prevStage.stdenv) cc fetchurl; + extraPath = [ prevStage.xz ]; + overrides = self: super: { inherit (prevStage) xz; }; + extraNativeBuildInputs = + if localSystem.isLinux then [ prevStage.patchelf ] else [ ]; + }; + }) + +] diff --git a/test/diff/idioms_pkgs_4/out.nix b/test/diff/idioms_pkgs_4/out.nix index a4ed06e4..717216df 100644 --- a/test/diff/idioms_pkgs_4/out.nix +++ b/test/diff/idioms_pkgs_4/out.nix @@ -84,9 +84,13 @@ let ] ++ ( if system == "i686-cygwin" then - [ ../cygwin/rebase-i686.sh ] + [ + ../cygwin/rebase-i686.sh + ] else if system == "x86_64-cygwin" then - [ ../cygwin/rebase-x86_64.sh ] + [ + ../cygwin/rebase-x86_64.sh + ] else [ ] ); @@ -197,9 +201,13 @@ in # First build a stdenv based only on tools outside the store. (prevStage: { inherit config overlays; - stdenv = makeStdenv { inherit (prevStage) cc fetchurl; } // { - inherit (prevStage) fetchurl; - }; + stdenv = + makeStdenv { + inherit (prevStage) cc fetchurl; + } + // { + inherit (prevStage) fetchurl; + }; }) # Using that, build a stdenv that adds the ‘xz’ command (which most systems diff --git a/test/diff/idioms_pkgs_5/out-pure.nix b/test/diff/idioms_pkgs_5/out-pure.nix new file mode 100644 index 00000000..fc02b21a --- /dev/null +++ b/test/diff/idioms_pkgs_5/out-pure.nix @@ -0,0 +1,796 @@ +{ lib, config }: + +stdenv: + +let + # Lib attributes are inherited to the lexical scope for performance reasons. + inherit (lib) + any + assertMsg + attrNames + boolToString + chooseDevOutputs + concatLists + concatMap + concatMapStrings + concatStringsSep + elem + elemAt + extendDerivation + filter + findFirst + flip + head + imap1 + isAttrs + isBool + isDerivation + isInt + isList + isString + mapAttrs + mapNullable + optional + optionalAttrs + optionalString + optionals + remove + splitString + subtractLists + unique + ; + + checkMeta = import ./check-meta.nix { + inherit lib config; + # Nix itself uses the `system` field of a derivation to decide where + # to build it. This is a bit confusing for cross compilation. + inherit (stdenv) hostPlatform; + }; + + # Based off lib.makeExtensible, with modifications: + makeDerivationExtensible = + rattrs: + let + # NOTE: The following is a hint that will be printed by the Nix cli when + # encountering an infinite recursion. It must not be formatted into + # separate lines, because Nix would only show the last line of the comment. + + # An infinite recursion here can be caused by having the attribute names of expression `e` in `.overrideAttrs(finalAttrs: previousAttrs: e)` depend on `finalAttrs`. Only the attribute values of `e` can depend on `finalAttrs`. + args = rattrs (args // { inherit finalPackage overrideAttrs; }); + # ^^^^ + + overrideAttrs = + f0: + let + f = + self: super: + # Convert f0 to an overlay. Legacy is: + # overrideAttrs (super: {}) + # We want to introduce self. We follow the convention of overlays: + # overrideAttrs (self: super: {}) + # Which means the first parameter can be either self or super. + # This is surprising, but far better than the confusion that would + # arise from flipping an overlay's parameters in some cases. + let + x = f0 super; + in + if builtins.isFunction x then + # Can't reuse `x`, because `self` comes first. + # Looks inefficient, but `f0 super` was a cheap thunk. + f0 self super + else + x; + in + makeDerivationExtensible ( + self: + let + super = rattrs self; + in + super // (if builtins.isFunction f0 || f0 ? __functor then f self super else f0) + ); + + finalPackage = mkDerivationSimple overrideAttrs args; + + in + finalPackage; + + #makeDerivationExtensibleConst = attrs: makeDerivationExtensible (_: attrs); + # but pre-evaluated for a slight improvement in performance. + makeDerivationExtensibleConst = + attrs: + mkDerivationSimple ( + f0: + let + f = + self: super: + let + x = f0 super; + in + if builtins.isFunction x then f0 self super else x; + in + makeDerivationExtensible ( + self: + attrs // (if builtins.isFunction f0 || f0 ? __functor then f self attrs else f0) + ) + ) attrs; + + mkDerivationSimple = + overrideAttrs: + + # `mkDerivation` wraps the builtin `derivation` function to + # produce derivations that use this stdenv and its shell. + # + # See also: + # + # * https://nixos.org/nixpkgs/manual/#sec-using-stdenv + # Details on how to use this mkDerivation function + # + # * https://nixos.org/manual/nix/stable/expressions/derivations.html#derivations + # Explanation about derivations in general + { + + # These types of dependencies are all exhaustively documented in + # the "Specifying Dependencies" section of the "Standard + # Environment" chapter of the Nixpkgs manual. + + # TODO(@Ericson2314): Stop using legacy dep attribute names + + # host offset -> target offset + depsBuildBuild ? [ ], # -1 -> -1 + depsBuildBuildPropagated ? [ ], # -1 -> -1 + nativeBuildInputs ? [ ], # -1 -> 0 N.B. Legacy name + propagatedNativeBuildInputs ? [ ], # -1 -> 0 N.B. Legacy name + depsBuildTarget ? [ ], # -1 -> 1 + depsBuildTargetPropagated ? [ ], # -1 -> 1 + + depsHostHost ? [ ], # 0 -> 0 + depsHostHostPropagated ? [ ], # 0 -> 0 + buildInputs ? [ ], # 0 -> 1 N.B. Legacy name + propagatedBuildInputs ? [ ], # 0 -> 1 N.B. Legacy name + + depsTargetTarget ? [ ], # 1 -> 1 + depsTargetTargetPropagated ? [ ], # 1 -> 1 + + checkInputs ? [ ], + installCheckInputs ? [ ], + nativeCheckInputs ? [ ], + nativeInstallCheckInputs ? [ ], + + # Configure Phase + configureFlags ? [ ], + cmakeFlags ? [ ], + mesonFlags ? [ ], + # Target is not included by default because most programs don't care. + # Including it then would cause needless mass rebuilds. + # + # TODO(@Ericson2314): Make [ "build" "host" ] always the default / resolve #87909 + configurePlatforms ? + optionals + ( + stdenv.hostPlatform != stdenv.buildPlatform + || config.configurePlatformsByDefault + ) + [ + "build" + "host" + ], + + # TODO(@Ericson2314): Make unconditional / resolve #33599 + # Check phase + doCheck ? config.doCheckByDefault or false, + + # TODO(@Ericson2314): Make unconditional / resolve #33599 + # InstallCheck phase + doInstallCheck ? config.doCheckByDefault or false, + + # TODO(@Ericson2314): Make always true and remove / resolve #178468 + strictDeps ? + if config.strictDepsByDefault then + true + else + stdenv.hostPlatform != stdenv.buildPlatform, + + enableParallelBuilding ? config.enableParallelBuildingByDefault, + + meta ? { }, + passthru ? { }, + pos ? # position used in error messages and for meta.position + ( + if attrs.meta.description or null != null then + builtins.unsafeGetAttrPos "description" attrs.meta + else if attrs.version or null != null then + builtins.unsafeGetAttrPos "version" attrs + else + builtins.unsafeGetAttrPos "name" attrs + ), + separateDebugInfo ? false, + outputs ? [ "out" ], + __darwinAllowLocalNetworking ? false, + __impureHostDeps ? [ ], + __propagatedImpureHostDeps ? [ ], + sandboxProfile ? "", + propagatedSandboxProfile ? "", + + hardeningEnable ? [ ], + hardeningDisable ? [ ], + + patches ? [ ], + + __contentAddressed ? + (!attrs ? outputHash) # Fixed-output drvs can't be content addressed too + && config.contentAddressedByDefault, + + # Experimental. For simple packages mostly just works, + # but for anything complex, be prepared to debug if enabling. + __structuredAttrs ? config.structuredAttrsByDefault or false, + + env ? { }, + + ... + }@attrs: + + # Policy on acceptable hash types in nixpkgs + assert + attrs ? outputHash + -> ( + let + algo = attrs.outputHashAlgo or (head (splitString "-" attrs.outputHash)); + in + if algo == "md5" then + throw "Rejected insecure ${algo} hash '${attrs.outputHash}'" + else + true + ); + + let + # TODO(@oxij, @Ericson2314): This is here to keep the old semantics, remove when + # no package has `doCheck = true`. + doCheck' = doCheck && stdenv.buildPlatform.canExecute stdenv.hostPlatform; + doInstallCheck' = + doInstallCheck && stdenv.buildPlatform.canExecute stdenv.hostPlatform; + + separateDebugInfo' = separateDebugInfo && stdenv.hostPlatform.isLinux; + outputs' = outputs ++ optional separateDebugInfo' "debug"; + + # Turn a derivation into its outPath without a string context attached. + # See the comment at the usage site. + unsafeDerivationToUntrackedOutpath = + drv: + if isDerivation drv then + builtins.unsafeDiscardStringContext drv.outPath + else + drv; + + noNonNativeDeps = + builtins.length ( + depsBuildTarget + ++ depsBuildTargetPropagated + ++ depsHostHost + ++ depsHostHostPropagated + ++ buildInputs + ++ propagatedBuildInputs + ++ depsTargetTarget + ++ depsTargetTargetPropagated + ) == 0; + dontAddHostSuffix = attrs ? outputHash && !noNonNativeDeps || !stdenv.hasCC; + + hardeningDisable' = + if + any (x: x == "fortify") hardeningDisable + # disabling fortify implies fortify3 should also be disabled + then + unique (hardeningDisable ++ [ "fortify3" ]) + else + hardeningDisable; + supportedHardeningFlags = [ + "fortify" + "fortify3" + "stackprotector" + "pie" + "pic" + "strictoverflow" + "format" + "relro" + "bindnow" + ]; + # Musl-based platforms will keep "pie", other platforms will not. + # If you change this, make sure to update section `{#sec-hardening-in-nixpkgs}` + # in the nixpkgs manual to inform users about the defaults. + defaultHardeningFlags = + if + stdenv.hostPlatform.isMusl + && + # Except when: + # - static aarch64, where compilation works, but produces segfaulting dynamically linked binaries. + # - static armv7l, where compilation fails. + !(stdenv.hostPlatform.isAarch && stdenv.hostPlatform.isStatic) + then + supportedHardeningFlags + else + remove "pie" supportedHardeningFlags; + enabledHardeningOptions = + if builtins.elem "all" hardeningDisable' then + [ ] + else + subtractLists hardeningDisable' (defaultHardeningFlags ++ hardeningEnable); + # hardeningDisable additionally supports "all". + erroneousHardeningFlags = subtractLists supportedHardeningFlags ( + hardeningEnable ++ remove "all" hardeningDisable + ); + + checkDependencyList = checkDependencyList' [ ]; + checkDependencyList' = + positions: name: deps: + flip imap1 deps ( + index: dep: + if + isDerivation dep || dep == null || builtins.isString dep || builtins.isPath dep + then + dep + else if isList dep then + checkDependencyList' ([ index ] ++ positions) name dep + else + throw "Dependency is not of a valid type: ${ + concatMapStrings (ix: "element ${toString ix} of ") ([ index ] ++ positions) + }${name} for ${attrs.name or attrs.pname}" + ); + in + if builtins.length erroneousHardeningFlags != 0 then + abort ( + "mkDerivation was called with unsupported hardening flags: " + + lib.generators.toPretty { } { + inherit + erroneousHardeningFlags + hardeningDisable + hardeningEnable + supportedHardeningFlags + ; + } + ) + else + let + doCheck = doCheck'; + doInstallCheck = doInstallCheck'; + buildInputs' = + buildInputs + ++ optionals doCheck checkInputs + ++ optionals doInstallCheck installCheckInputs; + nativeBuildInputs' = + nativeBuildInputs + ++ optional separateDebugInfo' ../../build-support/setup-hooks/separate-debug-info.sh + ++ optional stdenv.hostPlatform.isWindows ../../build-support/setup-hooks/win-dll-link.sh + ++ optionals doCheck nativeCheckInputs + ++ optionals doInstallCheck nativeInstallCheckInputs; + + outputs = outputs'; + + references = + nativeBuildInputs + ++ buildInputs + ++ propagatedNativeBuildInputs + ++ propagatedBuildInputs; + + dependencies = map (map chooseDevOutputs) [ + [ + (map (drv: drv.__spliced.buildBuild or drv) ( + checkDependencyList "depsBuildBuild" depsBuildBuild + )) + (map (drv: drv.__spliced.buildHost or drv) ( + checkDependencyList "nativeBuildInputs" nativeBuildInputs' + )) + (map (drv: drv.__spliced.buildTarget or drv) ( + checkDependencyList "depsBuildTarget" depsBuildTarget + )) + ] + [ + (map (drv: drv.__spliced.hostHost or drv) ( + checkDependencyList "depsHostHost" depsHostHost + )) + (map (drv: drv.__spliced.hostTarget or drv) ( + checkDependencyList "buildInputs" buildInputs' + )) + ] + [ + (map (drv: drv.__spliced.targetTarget or drv) ( + checkDependencyList "depsTargetTarget" depsTargetTarget + )) + ] + ]; + propagatedDependencies = map (map chooseDevOutputs) [ + [ + (map (drv: drv.__spliced.buildBuild or drv) ( + checkDependencyList "depsBuildBuildPropagated" depsBuildBuildPropagated + )) + (map (drv: drv.__spliced.buildHost or drv) ( + checkDependencyList "propagatedNativeBuildInputs" propagatedNativeBuildInputs + )) + (map (drv: drv.__spliced.buildTarget or drv) ( + checkDependencyList "depsBuildTargetPropagated" depsBuildTargetPropagated + )) + ] + [ + (map (drv: drv.__spliced.hostHost or drv) ( + checkDependencyList "depsHostHostPropagated" depsHostHostPropagated + )) + (map (drv: drv.__spliced.hostTarget or drv) ( + checkDependencyList "propagatedBuildInputs" propagatedBuildInputs + )) + ] + [ + (map (drv: drv.__spliced.targetTarget or drv) ( + checkDependencyList "depsTargetTargetPropagated" depsTargetTargetPropagated + )) + ] + ]; + + computedSandboxProfile = + concatMap (input: input.__propagatedSandboxProfile or [ ]) + ( + stdenv.extraNativeBuildInputs + ++ stdenv.extraBuildInputs + ++ concatLists dependencies + ); + + computedPropagatedSandboxProfile = concatMap ( + input: input.__propagatedSandboxProfile or [ ] + ) (concatLists propagatedDependencies); + + computedImpureHostDeps = unique ( + concatMap (input: input.__propagatedImpureHostDeps or [ ]) ( + stdenv.extraNativeBuildInputs + ++ stdenv.extraBuildInputs + ++ concatLists dependencies + ) + ); + + computedPropagatedImpureHostDeps = unique ( + concatMap (input: input.__propagatedImpureHostDeps or [ ]) ( + concatLists propagatedDependencies + ) + ); + + envIsExportable = isAttrs env && !isDerivation env; + + derivationArg = + (removeAttrs attrs ( + [ + "meta" + "passthru" + "pos" + "checkInputs" + "installCheckInputs" + "nativeCheckInputs" + "nativeInstallCheckInputs" + "__contentAddressed" + "__darwinAllowLocalNetworking" + "__impureHostDeps" + "__propagatedImpureHostDeps" + "sandboxProfile" + "propagatedSandboxProfile" + ] + ++ optional (__structuredAttrs || envIsExportable) "env" + )) + // (optionalAttrs (attrs ? name || (attrs ? pname && attrs ? version)) { + name = + let + # Indicate the host platform of the derivation if cross compiling. + # Fixed-output derivations like source tarballs shouldn't get a host + # suffix. But we have some weird ones with run-time deps that are + # just used for their side-affects. Those might as well since the + # hash can't be the same. See #32986. + hostSuffix = optionalString ( + stdenv.hostPlatform != stdenv.buildPlatform && !dontAddHostSuffix + ) "-${stdenv.hostPlatform.config}"; + + # Disambiguate statically built packages. This was originally + # introduce as a means to prevent nix-env to get confused between + # nix and nixStatic. This should be also achieved by moving the + # hostSuffix before the version, so we could contemplate removing + # it again. + staticMarker = optionalString stdenv.hostPlatform.isStatic "-static"; + in + lib.strings.sanitizeDerivationName ( + if attrs ? name then + attrs.name + hostSuffix + else + # we cannot coerce null to a string below + assert assertMsg ( + attrs ? version && attrs.version != null + ) "The ‘version’ attribute cannot be null."; + "${attrs.pname}${staticMarker}${hostSuffix}-${attrs.version}" + ); + }) + // optionalAttrs __structuredAttrs { env = checkedEnv; } + // { + builder = attrs.realBuilder or stdenv.shell; + args = + attrs.args or [ + "-e" + (attrs.builder or ./default-builder.sh) + ]; + inherit stdenv; + + # The `system` attribute of a derivation has special meaning to Nix. + # Derivations set it to choose what sort of machine could be used to + # execute the build, The build platform entirely determines this, + # indeed more finely than Nix knows or cares about. The `system` + # attribute of `buildPlatfom` matches Nix's degree of specificity. + # exactly. + inherit (stdenv.buildPlatform) system; + + userHook = config.stdenv.userHook or null; + __ignoreNulls = true; + inherit __structuredAttrs strictDeps; + + depsBuildBuild = elemAt (elemAt dependencies 0) 0; + nativeBuildInputs = elemAt (elemAt dependencies 0) 1; + depsBuildTarget = elemAt (elemAt dependencies 0) 2; + depsHostHost = elemAt (elemAt dependencies 1) 0; + buildInputs = elemAt (elemAt dependencies 1) 1; + depsTargetTarget = elemAt (elemAt dependencies 2) 0; + + depsBuildBuildPropagated = elemAt (elemAt propagatedDependencies 0) 0; + propagatedNativeBuildInputs = elemAt (elemAt propagatedDependencies 0) 1; + depsBuildTargetPropagated = elemAt (elemAt propagatedDependencies 0) 2; + depsHostHostPropagated = elemAt (elemAt propagatedDependencies 1) 0; + propagatedBuildInputs = elemAt (elemAt propagatedDependencies 1) 1; + depsTargetTargetPropagated = elemAt (elemAt propagatedDependencies 2) 0; + + # This parameter is sometimes a string, sometimes null, and sometimes a list, yuck + configureFlags = + configureFlags + ++ optional (elem "build" configurePlatforms) "--build=${stdenv.buildPlatform.config}" + ++ optional (elem "host" configurePlatforms) "--host=${stdenv.hostPlatform.config}" + ++ optional (elem "target" configurePlatforms) "--target=${stdenv.targetPlatform.config}"; + + cmakeFlags = + cmakeFlags + ++ optionals (stdenv.hostPlatform != stdenv.buildPlatform) ( + [ + "-DCMAKE_SYSTEM_NAME=${ + findFirst isString "Generic" ( + optional (!stdenv.hostPlatform.isRedox) stdenv.hostPlatform.uname.system + ) + }" + ] + ++ optionals (stdenv.hostPlatform.uname.processor != null) [ + "-DCMAKE_SYSTEM_PROCESSOR=${stdenv.hostPlatform.uname.processor}" + ] + ++ optionals (stdenv.hostPlatform.uname.release != null) [ + "-DCMAKE_SYSTEM_VERSION=${stdenv.hostPlatform.uname.release}" + ] + ++ optionals (stdenv.hostPlatform.isDarwin) [ + "-DCMAKE_OSX_ARCHITECTURES=${stdenv.hostPlatform.darwinArch}" + ] + ++ optionals (stdenv.buildPlatform.uname.system != null) [ + "-DCMAKE_HOST_SYSTEM_NAME=${stdenv.buildPlatform.uname.system}" + ] + ++ optionals (stdenv.buildPlatform.uname.processor != null) [ + "-DCMAKE_HOST_SYSTEM_PROCESSOR=${stdenv.buildPlatform.uname.processor}" + ] + ++ optionals (stdenv.buildPlatform.uname.release != null) [ + "-DCMAKE_HOST_SYSTEM_VERSION=${stdenv.buildPlatform.uname.release}" + ] + ++ optionals (stdenv.buildPlatform.canExecute stdenv.hostPlatform) [ + "-DCMAKE_CROSSCOMPILING_EMULATOR=env" + ] + ); + + mesonFlags = + let + # See https://mesonbuild.com/Reference-tables.html#cpu-families + cpuFamily = + platform: + with platform; + if isAarch32 then + "arm" + else if isx86_32 then + "x86" + else + platform.uname.processor; + + crossFile = builtins.toFile "cross-file.conf" '' + [properties] + needs_exe_wrapper = ${ + boolToString (!stdenv.buildPlatform.canExecute stdenv.hostPlatform) + } + + [host_machine] + system = '${stdenv.targetPlatform.parsed.kernel.name}' + cpu_family = '${cpuFamily stdenv.targetPlatform}' + cpu = '${stdenv.targetPlatform.parsed.cpu.name}' + endian = ${if stdenv.targetPlatform.isLittleEndian then "'little'" else "'big'"} + + [binaries] + llvm-config = 'llvm-config-native' + ''; + crossFlags = optionals (stdenv.hostPlatform != stdenv.buildPlatform) [ + "--cross-file=${crossFile}" + ]; + in + crossFlags ++ mesonFlags; + + inherit patches; + + inherit doCheck doInstallCheck; + + inherit outputs; + } + // optionalAttrs (__contentAddressed) { + inherit __contentAddressed; + # Provide default values for outputHashMode and outputHashAlgo because + # most people won't care about these anyways + outputHashAlgo = attrs.outputHashAlgo or "sha256"; + outputHashMode = attrs.outputHashMode or "recursive"; + } + // optionalAttrs (enableParallelBuilding) { + inherit enableParallelBuilding; + enableParallelChecking = attrs.enableParallelChecking or true; + enableParallelInstalling = attrs.enableParallelInstalling or true; + } + // optionalAttrs ( + hardeningDisable != [ ] || hardeningEnable != [ ] || stdenv.hostPlatform.isMusl + ) { NIX_HARDENING_ENABLE = enabledHardeningOptions; } + // + optionalAttrs (stdenv.hostPlatform.isx86_64 && stdenv.hostPlatform ? gcc.arch) + { + requiredSystemFeatures = attrs.requiredSystemFeatures or [ ] ++ [ + "gccarch-${stdenv.hostPlatform.gcc.arch}" + ]; + } + // optionalAttrs (stdenv.buildPlatform.isDarwin) { + inherit __darwinAllowLocalNetworking; + # TODO: remove `unique` once nix has a list canonicalization primitive + __sandboxProfile = + let + profiles = + [ stdenv.extraSandboxProfile ] + ++ computedSandboxProfile + ++ computedPropagatedSandboxProfile + ++ [ + propagatedSandboxProfile + sandboxProfile + ]; + final = concatStringsSep "\n" (filter (x: x != "") (unique profiles)); + in + final; + __propagatedSandboxProfile = unique ( + computedPropagatedSandboxProfile ++ [ propagatedSandboxProfile ] + ); + __impureHostDeps = + computedImpureHostDeps + ++ computedPropagatedImpureHostDeps + ++ __propagatedImpureHostDeps + ++ __impureHostDeps + ++ stdenv.__extraImpureHostDeps + ++ [ + "/dev/zero" + "/dev/random" + "/dev/urandom" + "/bin/sh" + ]; + __propagatedImpureHostDeps = + computedPropagatedImpureHostDeps ++ __propagatedImpureHostDeps; + } + // + # If we use derivations directly here, they end up as build-time dependencies. + # This is especially problematic in the case of disallowed*, since the disallowed + # derivations will be built by nix as build-time dependencies, while those + # derivations might take a very long time to build, or might not even build + # successfully on the platform used. + # We can improve on this situation by instead passing only the outPath, + # without an attached string context, to nix. The out path will be a placeholder + # which will be replaced by the actual out path if the derivation in question + # is part of the final closure (and thus needs to be built). If it is not + # part of the final closure, then the placeholder will be passed along, + # but in that case we know for a fact that the derivation is not part of the closure. + # This means that passing the out path to nix does the right thing in either + # case, both for disallowed and allowed references/requisites, and we won't + # build the derivation if it wouldn't be part of the closure, saving time and resources. + # While the problem is less severe for allowed*, since we want the derivation + # to be built eventually, we would still like to get the error early and without + # having to wait while nix builds a derivation that might not be used. + # See also https://github.com/NixOS/nix/issues/4629 + optionalAttrs (attrs ? disallowedReferences) { + disallowedReferences = map unsafeDerivationToUntrackedOutpath attrs.disallowedReferences; + } + // optionalAttrs (attrs ? disallowedRequisites) { + disallowedRequisites = map unsafeDerivationToUntrackedOutpath attrs.disallowedRequisites; + } + // optionalAttrs (attrs ? allowedReferences) { + allowedReferences = mapNullable unsafeDerivationToUntrackedOutpath attrs.allowedReferences; + } + // optionalAttrs (attrs ? allowedRequisites) { + allowedRequisites = mapNullable unsafeDerivationToUntrackedOutpath attrs.allowedRequisites; + }; + + meta = checkMeta.commonMeta { + inherit + validity + attrs + pos + references + ; + }; + validity = checkMeta.assertValidity { inherit meta attrs; }; + + checkedEnv = + let + overlappingNames = attrNames (builtins.intersectAttrs env derivationArg); + in + assert assertMsg envIsExportable + "When using structured attributes, `env` must be an attribute set of environment variables."; + assert assertMsg (overlappingNames == [ ]) + "The ‘env’ attribute set cannot contain any attributes passed to derivation. The following attributes are overlapping: ${concatStringsSep ", " overlappingNames}"; + mapAttrs ( + n: v: + assert assertMsg (isString v || isBool v || isInt v || isDerivation v) + "The ‘env’ attribute set can only contain derivation, string, boolean or integer attributes. The ‘${n}’ attribute is of type ${builtins.typeOf v}."; + v + ) env; + + in + + extendDerivation validity.handled ( + { + # A derivation that always builds successfully and whose runtime + # dependencies are the original derivations build time dependencies + # This allows easy building and distributing of all derivations + # needed to enter a nix-shell with + # nix-build shell.nix -A inputDerivation + inputDerivation = derivation ( + derivationArg + // { + # Add a name in case the original drv didn't have one + name = derivationArg.name or "inputDerivation"; + # This always only has one output + outputs = [ "out" ]; + + # Propagate the original builder and arguments, since we override + # them and they might contain references to build inputs + _derivation_original_builder = derivationArg.builder; + _derivation_original_args = derivationArg.args; + + builder = stdenv.shell; + # The bash builtin `export` dumps all current environment variables, + # which is where all build input references end up (e.g. $PATH for + # binaries). By writing this to $out, Nix can find and register + # them as runtime dependencies (since Nix greps for store paths + # through $out to find them) + args = [ + "-c" + '' + export > $out + for var in $passAsFile; do + pathVar="''${var}Path" + printf "%s" "$(< "''${!pathVar}")" >> $out + done + '' + ]; + + # inputDerivation produces the inputs; not the outputs, so any + # restrictions on what used to be the outputs don't serve a purpose + # anymore. + allowedReferences = null; + allowedRequisites = null; + disallowedReferences = [ ]; + disallowedRequisites = [ ]; + } + ); + + inherit passthru overrideAttrs; + inherit meta; + } + // + # Pass through extra attributes that are not inputs, but + # should be made available to Nix expressions using the + # derivation (e.g., in assertions). + passthru + ) (derivation (derivationArg // optionalAttrs envIsExportable checkedEnv)); + +in +fnOrAttrs: +if builtins.isFunction fnOrAttrs then + makeDerivationExtensible fnOrAttrs +else + makeDerivationExtensibleConst fnOrAttrs diff --git a/test/diff/idioms_pkgs_5/out.nix b/test/diff/idioms_pkgs_5/out.nix index fc02b21a..eab21af3 100644 --- a/test/diff/idioms_pkgs_5/out.nix +++ b/test/diff/idioms_pkgs_5/out.nix @@ -628,9 +628,14 @@ let enableParallelChecking = attrs.enableParallelChecking or true; enableParallelInstalling = attrs.enableParallelInstalling or true; } - // optionalAttrs ( - hardeningDisable != [ ] || hardeningEnable != [ ] || stdenv.hostPlatform.isMusl - ) { NIX_HARDENING_ENABLE = enabledHardeningOptions; } + // + optionalAttrs + ( + hardeningDisable != [ ] || hardeningEnable != [ ] || stdenv.hostPlatform.isMusl + ) + { + NIX_HARDENING_ENABLE = enabledHardeningOptions; + } // optionalAttrs (stdenv.hostPlatform.isx86_64 && stdenv.hostPlatform ? gcc.arch) { diff --git a/test/diff/if_else/out-pure.nix b/test/diff/if_else/out-pure.nix new file mode 100644 index 00000000..479cd610 --- /dev/null +++ b/test/diff/if_else/out-pure.nix @@ -0,0 +1,119 @@ +[ + (if true then { version = "1.2.3"; } else { version = "3.2.1"; }) + ( + if true then + '' + some text + '' + else + '' + other text + '' + ) + (if ./a then b else c) + (if a then b else c) + ( + # test + if + a # test + then # test + b # test + # test + else + c + ) + ( + # test + if + a # test + then # test + b # test + # test + else + c + ) + ( + if + [ + multiline + # tmp + condition + ] + then + foo + else if + [ + more + multi + line + ] + then + bar + else + baz + ) + ( + if + unabsorbable # comment + == multiline + then + foo + else if + unabsorbable # comment + == multiline + then + bar + else + baz + ) + ( + if if a then b else c then + b + else if a then + b + else if a then + b + else + c + ) + ( + if if a then b else c then + b + else if a then + b + # x + else if a then + b + else + c + ) + ( + if + ( + if + (if (if a then b else c) then (if a then b else c) else (if a then b else c)) + then + (if (if a then b else c) then (if a then b else c) else (if a then b else c)) + else + (if (if a then b else c) then (if a then b else c) else (if a then b else c)) + ) + then + ( + if + (if (if a then b else c) then (if a then b else c) else (if a then b else c)) + then + (if (if a then b else c) then (if a then b else c) else (if a then b else c)) + else + (if (if a then b else c) then (if a then b else c) else (if a then b else c)) + ) + else + ( + if + (if (if a then b else c) then (if a then b else c) else (if a then b else c)) + then + (if (if a then b else c) then (if a then b else c) else (if a then b else c)) + else + (if (if a then b else c) then (if a then b else c) else (if a then b else c)) + ) + ) +] diff --git a/test/diff/if_else/out.nix b/test/diff/if_else/out.nix index 479cd610..15848854 100644 --- a/test/diff/if_else/out.nix +++ b/test/diff/if_else/out.nix @@ -1,5 +1,14 @@ [ - (if true then { version = "1.2.3"; } else { version = "3.2.1"; }) + ( + if true then + { + version = "1.2.3"; + } + else + { + version = "3.2.1"; + } + ) ( if true then '' diff --git a/test/diff/inherit/in.nix b/test/diff/inherit/in.nix index a66fc107..a5088d4c 100644 --- a/test/diff/inherit/in.nix +++ b/test/diff/inherit/in.nix @@ -29,4 +29,13 @@ h ; } + + { + inherit + ; + inherit + a; + inherit a + ; + } ] diff --git a/test/diff/inherit/out-pure.nix b/test/diff/inherit/out-pure.nix new file mode 100644 index 00000000..287f449d --- /dev/null +++ b/test/diff/inherit/out-pure.nix @@ -0,0 +1,86 @@ +[ + { + # empty inherit o.O + inherit ; + inherit aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa; + } + { + inherit + a + b + c + d + e + f + g + h + i + j + ; + } + { inherit aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa; } + { inherit b d; } + { + inherit + b + d # e + ; + } + { + inherit + b # c + d + ; + } + { + inherit + b # c + d # e + ; + } + { + inherit # a + b + d + ; + } + { + inherit # a + b + d # e + ; + } + { + inherit # a + b # c + d + ; + } + { + inherit # a + b # c + d # e + ; + } + { + inherit # test + a # test + + b # test + c # test + d # test + + e + f + + g + h + ; + } + + { + inherit ; + inherit a; + inherit a; + } +] diff --git a/test/diff/inherit/out.nix b/test/diff/inherit/out.nix index 93a31869..a15a258d 100644 --- a/test/diff/inherit/out.nix +++ b/test/diff/inherit/out.nix @@ -1,7 +1,7 @@ [ { # empty inherit o.O - inherit; + inherit ; inherit aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa; } { @@ -18,7 +18,11 @@ j ; } - { inherit aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa; } + { + inherit + aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa + ; + } { inherit b d; } { inherit @@ -77,4 +81,15 @@ h ; } + + { + inherit + ; + inherit + a + ; + inherit + a + ; + } ] diff --git a/test/diff/inherit_blank_trailing/out-pure.nix b/test/diff/inherit_blank_trailing/out-pure.nix new file mode 100644 index 00000000..7e8b2469 --- /dev/null +++ b/test/diff/inherit_blank_trailing/out-pure.nix @@ -0,0 +1,33 @@ +[ + { + inherit # test + a # test + + b # test + c # test + d # test + + e + f + + g + h + ; + } + { + inherit + a # mixed trivialities + + # comment 1 + # comment 2 + + # comment 3 after blanks + b # multiple newlines + + c # multiple comments + # comment 1 + # comment 2 + # comment 3 + ; + } +] diff --git a/test/diff/inherit_comment/out-pure.nix b/test/diff/inherit_comment/out-pure.nix new file mode 100644 index 00000000..45c2bb99 --- /dev/null +++ b/test/diff/inherit_comment/out-pure.nix @@ -0,0 +1,18 @@ +{ + inherit # eeby deeby + a + # b + c + ; + + # https://github.com/kamadorueda/alejandra/issues/372 + inherit (pkgs.haskell.lib) + # doJailbreak - remove package bounds from build-depends of a package + doJailbreak + # dontCheck - skip tests + dontCheck + # override deps of a package + # see what can be overriden - https://github.com/NixOS/nixpkgs/blob/0ba44a03f620806a2558a699dba143e6cf9858db/pkgs/development/haskell-modules/generic-builder.nix#L13 + overrideCabal + ; +} diff --git a/test/diff/inherit_from/in.nix b/test/diff/inherit_from/in.nix index 6b375f1c..ea9d0e6e 100644 --- a/test/diff/inherit_from/in.nix +++ b/test/diff/inherit_from/in.nix @@ -75,4 +75,17 @@ { inherit /*a*/ (/*b*/ c /*d*/) /*e*/ f h /*i*/; } { inherit /*a*/ (/*b*/ c /*d*/) /*e*/ f /*g*/ h ; } { inherit /*a*/ (/*b*/ c /*d*/) /*e*/ f /*g*/ h /*i*/; } + { + inherit ({}) ; + inherit ({}) + ; + inherit + ({}); + + inherit ({}) a; + inherit ({}) a + ; + inherit ({}) + a; + } ] diff --git a/test/diff/inherit_from/out-pure.nix b/test/diff/inherit_from/out-pure.nix new file mode 100644 index 00000000..de104811 --- /dev/null +++ b/test/diff/inherit_from/out-pure.nix @@ -0,0 +1,583 @@ +[ + { + # empty inherit o.O + inherit (geany.meta) ; + inherit (builtins) + pathExists + readFile + isBool + isInt + isFloat + add + sub + lessThan + seq + deepSeq + genericClosure + ; + } + { + inherit + ({ + foo = "1"; + bar = "2"; # force multiline + }) + foo + bar + ; + } + { + inherit (a) + b + c + d + e + f + g + h + i + j + k + ; + } + { inherit (c) f h; } + { + inherit (c) + f + h # i + ; + } + { + inherit (c) + f # g + h + ; + } + { + inherit (c) + f # g + h # i + ; + } + { + inherit (c) # e + f + h + ; + } + { + inherit (c) # e + f + h # i + ; + } + { + inherit (c) # e + f # g + h + ; + } + { + inherit (c) # e + f # g + h # i + ; + } + { + inherit + ( + c # d + ) + f + h + ; + } + { + inherit + ( + c # d + ) + f + h # i + ; + } + { + inherit + ( + c # d + ) + f # g + h + ; + } + { + inherit + ( + c # d + ) + f # g + h # i + ; + } + { + inherit + ( + c # d + ) # e + f + h + ; + } + { + inherit + ( + c # d + ) # e + f + h # i + ; + } + { + inherit + ( + c # d + ) # e + f # g + h + ; + } + { + inherit + ( + c # d + ) # e + f # g + h # i + ; + } + { + inherit + # b + (c) + f + h + ; + } + { + inherit + # b + (c) + f + h # i + ; + } + { + inherit + # b + (c) + f # g + h + ; + } + { + inherit + # b + (c) + f # g + h # i + ; + } + { + inherit + # b + (c) # e + f + h + ; + } + { + inherit + # b + (c) # e + f + h # i + ; + } + { + inherit + # b + (c) # e + f # g + h + ; + } + { + inherit + # b + (c) # e + f # g + h # i + ; + } + { + inherit + # b + ( + c # d + ) + f + h + ; + } + { + inherit + # b + ( + c # d + ) + f + h # i + ; + } + { + inherit + # b + ( + c # d + ) + f # g + h + ; + } + { + inherit + # b + ( + c # d + ) + f # g + h # i + ; + } + { + inherit + # b + ( + c # d + ) # e + f + h + ; + } + { + inherit + # b + ( + c # d + ) # e + f + h # i + ; + } + { + inherit + # b + ( + c # d + ) # e + f # g + h + ; + } + { + inherit + # b + ( + c # d + ) # e + f # g + h # i + ; + } + { + inherit # a + (c) + f + h + ; + } + { + inherit # a + (c) + f + h # i + ; + } + { + inherit # a + (c) + f # g + h + ; + } + { + inherit # a + (c) + f # g + h # i + ; + } + { + inherit # a + (c) # e + f + h + ; + } + { + inherit # a + (c) # e + f + h # i + ; + } + { + inherit # a + (c) # e + f # g + h + ; + } + { + inherit # a + (c) # e + f # g + h # i + ; + } + { + inherit # a + ( + c # d + ) + f + h + ; + } + { + inherit # a + ( + c # d + ) + f + h # i + ; + } + { + inherit # a + ( + c # d + ) + f # g + h + ; + } + { + inherit # a + ( + c # d + ) + f # g + h # i + ; + } + { + inherit # a + ( + c # d + ) # e + f + h + ; + } + { + inherit # a + ( + c # d + ) # e + f + h # i + ; + } + { + inherit # a + ( + c # d + ) # e + f # g + h + ; + } + { + inherit # a + ( + c # d + ) # e + f # g + h # i + ; + } + { + inherit # a + # b + (c) + f + h + ; + } + { + inherit # a + # b + (c) + f + h # i + ; + } + { + inherit # a + # b + (c) + f # g + h + ; + } + { + inherit # a + # b + (c) + f # g + h # i + ; + } + { + inherit # a + # b + (c) # e + f + h + ; + } + { + inherit # a + # b + (c) # e + f + h # i + ; + } + { + inherit # a + # b + (c) # e + f # g + h + ; + } + { + inherit # a + # b + (c) # e + f # g + h # i + ; + } + { + inherit # a + # b + ( + c # d + ) + f + h + ; + } + { + inherit # a + # b + ( + c # d + ) + f + h # i + ; + } + { + inherit # a + # b + ( + c # d + ) + f # g + h + ; + } + { + inherit # a + # b + ( + c # d + ) + f # g + h # i + ; + } + { + inherit # a + # b + ( + c # d + ) # e + f + h + ; + } + { + inherit # a + # b + ( + c # d + ) # e + f + h # i + ; + } + { + inherit # a + # b + ( + c # d + ) # e + f # g + h + ; + } + { + inherit # a + # b + ( + c # d + ) # e + f # g + h # i + ; + } + { + inherit ({ }) ; + inherit ({ }) ; + inherit ({ }) ; + + inherit ({ }) a; + inherit ({ }) a; + inherit ({ }) a; + } +] diff --git a/test/diff/inherit_from/out.nix b/test/diff/inherit_from/out.nix index 126b8f8b..f53312f6 100644 --- a/test/diff/inherit_from/out.nix +++ b/test/diff/inherit_from/out.nix @@ -1,7 +1,7 @@ [ { # empty inherit o.O - inherit (geany.meta); + inherit (geany.meta) ; inherit (builtins) pathExists readFile @@ -571,4 +571,19 @@ h # i ; } + { + inherit ({ }) ; + inherit ({ }) + ; + inherit ({ }) + ; + + inherit ({ }) a; + inherit ({ }) + a + ; + inherit ({ }) + a + ; + } ] diff --git a/test/diff/key_value/out-pure.nix b/test/diff/key_value/out-pure.nix new file mode 100644 index 00000000..1d93de5b --- /dev/null +++ b/test/diff/key_value/out-pure.nix @@ -0,0 +1,71 @@ +rec { + + a = (((4))); + a = (((a: b))); + + a = { + a = 1; + }; + + b = { + a = 1 # d + ; + }; + + c = { + a = # c + 1; + }; + d = { + a = # c + 1 # d + ; + }; + e = { + a # b + = 1; + }; + f = { + a # b + = 1 # d + ; + }; + h = { + a # b + = # c + 1; + }; + i = { + a # b + = # c + 1 # d + ; + }; + j = a: { b = 1; }; + k = a: { + b = 1; + c = 2; + }; + l = + a: # b + { b = 1; }; + m = + a: # b + { + b = 1; + c = 2; + }; + n = pkgs: { }; + o = { pkgs, ... }: { }; + + a + # b + = + # c + 1 + # d + ; + + p = aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa { } a; + +} diff --git a/test/diff/key_value/out.nix b/test/diff/key_value/out.nix index 1d93de5b..0ced3361 100644 --- a/test/diff/key_value/out.nix +++ b/test/diff/key_value/out.nix @@ -56,7 +56,12 @@ rec { c = 2; }; n = pkgs: { }; - o = { pkgs, ... }: { }; + o = + { + pkgs, + ... + }: + { }; a # b diff --git a/test/diff/lambda/in.nix b/test/diff/lambda/in.nix index 12d30655..0f7f7a5c 100644 --- a/test/diff/lambda/in.nix +++ b/test/diff/lambda/in.nix @@ -2,6 +2,13 @@ let inherit lib; in [ + ({}: null) + ({ + }: null) + ({ + + }: null) + ( { lib, }: let diff --git a/test/diff/lambda/out-pure.nix b/test/diff/lambda/out-pure.nix new file mode 100644 index 00000000..5d888163 --- /dev/null +++ b/test/diff/lambda/out-pure.nix @@ -0,0 +1,222 @@ +let + inherit lib; +in +[ + ({ }: null) + ({ }: null) + ( + { + + }: + null + ) + + ( + { lib }: + let + foo = 1; + in + foo + ) + ( + /* + Collection of functions useful for debugging + Some comment + */ + { lib }: + let + foo = 1; + in + foo + ) + ( + a: b: # c + d + ) + ( + { }: + b: # c + d + ) + ( + a: + { }: # c + d + ) + (a: d) + ( + a: # c + d + ) + ( + a # b + : + d + ) + ( + a # b + : # c + d + ) + (aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa: aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa) + (aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa: aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa) + ( + { + pkgs ? import ./.. { }, + locationsXml, + }: + null + ) + ( + a: b: c: + { }: + a: b: c: + a + ) + + ( + { pkgs, ... }: + { + # Stuff + } + ) + + ( + { pkgs, ... }: + let + in + pkgs + ) + + ( + a: + { b, ... }: + c: { + # Stuff + } + ) + + ( + a: + { b, c, ... }: + d: { + # Stuff + } + ) + + ( + { + gst_plugins ? [ + gst-plugins-good + gst-plugins-ugly + ], + more ? + let + in + [ + 1 + 2 + 3 + ], + things ? if null then true else false, + things ? + if null then true else "loooooooooooooooooooooooooooooooooooooooooooong", + more ? ( + let + in + [ + 1 + 2 + 3 + ] + ), + foo ? ( + with bar; + [ + 1 + 2 + 3 + ] + ), + foo ? ( + with bar; + let + in + [ + 1 + 2 + 3 + ] + ), + things ? (if null then true else false), + things ? ( + if null then true else "loooooooooooooooooooooooooooooooooooooooooooong" + ), + things ? ( + if null then + [ + 1 + 2 + 3 + ] + else + "loooooooooooooooooooooooooooooooooooooooooooong" + ), + things ? # comment + ( + if null then + [ + 1 + 2 + 3 + ] + else + "loooooooooooooooooooooooooooooooooooooooooooong" + ), + }: + { } + ) + { + a = + name: with config.ids; '' + --nodaemon --syslog --prefix=${name} --pidfile /run/${name}/${name}.pid ${name} + ''; + a' = name: '' + --nodaemon --syslog --prefix=${name} --pidfile /run/${name}/${name}.pid ${name} + ''; + b = + p: with p; [ + ConfigIniFiles + FileSlurp + ]; + b' = p: [ + ConfigIniFiles + FileSlurp + ]; + mkUrls = + { + name, + version, + biocVersion, + }: + [ "mirror://bioc/${biocVersion}/data/experiment/${name}_${version}.tar.gz" ]; + c = + { ... }: + { + foo = true; + }; + c = { ... }: [ 1 ]; + d = + { a }: + { + foo = true; + }; + d = { a }: [ 1 ]; + e = + { a, b }: + { + foo = true; + }; + e = { a, b }: [ 1 ]; + } +] diff --git a/test/diff/lambda/out.nix b/test/diff/lambda/out.nix index 64078167..16eb44de 100644 --- a/test/diff/lambda/out.nix +++ b/test/diff/lambda/out.nix @@ -2,6 +2,19 @@ let inherit lib; in [ + ({ }: null) + ( + { + }: + null + ) + ( + { + + }: + null + ) + ( { lib }: let @@ -81,7 +94,10 @@ in ( a: - { b, ... }: + { + b, + ... + }: c: { # Stuff } @@ -89,7 +105,11 @@ in ( a: - { b, c, ... }: + { + b, + c, + ... + }: d: { # Stuff } diff --git a/test/diff/let_in/out-pure.nix b/test/diff/let_in/out-pure.nix new file mode 100644 index 00000000..6870e5b3 --- /dev/null +++ b/test/diff/let_in/out-pure.nix @@ -0,0 +1,77 @@ +let + + a = + let + b = 2; + c = 3; + in + d; + a = + let + c = 1; + in + f; + + a = + let + c = 1; + in + # e + f; + a = + let + c = 1; # d + in + f; + + a = + let + c = 1; # d + in + # e + f; + a = + let # b + c = 1; + in + f; + a = + let # b + c = 1; + in + # e + f; + a = + let # b + c = 1; # d + in + f; + a = + let # b + c = 1; # d + in + # e + f; + + a = + let + in + [ + 1 + 2 + ]; + + a = + let + b = 0; + + in + # foo + # bar + # baz + # qux + null; + +in + +a diff --git a/test/diff/lists/in.nix b/test/diff/lists/in.nix index 012e7300..77a07401 100644 --- a/test/diff/lists/in.nix +++ b/test/diff/lists/in.nix @@ -1,4 +1,7 @@ [ + [] + [ + ] [ ] diff --git a/test/diff/lists/out-pure.nix b/test/diff/lists/out-pure.nix new file mode 100644 index 00000000..6bf6b5ae --- /dev/null +++ b/test/diff/lists/out-pure.nix @@ -0,0 +1,127 @@ +[ + [ ] + [ ] + [ + + ] + + [ + [ + + ] + ] + + [ + "string" + + ] + + [ + { + # multiline + foo = "bar"; + foo2 = "barbar"; + } + ] + { + # List in attrset with comment + + imports0 = [ ]; + + imports2 = [ + # ./disko.nix + ./hardware-configuration.nix + ]; + imports3 = [ + # comment + ./disko.nix + ./hardware-configuration.nix + ]; + } + [ + ( + if foo then + bar # multiline too + else + baz + ) + ] + [ 1 ] + + [ 1 ] + + [ + b + d + ] + [ + b + d # e + ] + [ + b # c + d + ] + [ + b # c + d # e + ] + [ + # a + b + d + ] + [ + # a + b + d # e + ] + [ + # a + b # c + d + ] + [ + # a + b # c + d # e + ] + + [ + + b + + d + + ] + [ + + # a + + b + + # c + + d + + # e + + ] + + [ + [ + multi + line + ] + ] + [ [ [ singleton ] ] ] + [ [ [ { } ] ] ] + [ + [ + [ + { } + multiline + ] + ] + ] +] diff --git a/test/diff/lists/out.nix b/test/diff/lists/out.nix index fed594cd..6798279b 100644 --- a/test/diff/lists/out.nix +++ b/test/diff/lists/out.nix @@ -1,4 +1,7 @@ [ + [ ] + [ + ] [ ] @@ -46,7 +49,9 @@ ] [ 1 ] - [ 1 ] + [ + 1 + ] [ b diff --git a/test/diff/monsters_1/out-pure.nix b/test/diff/monsters_1/out-pure.nix new file mode 100644 index 00000000..18183d4e --- /dev/null +++ b/test/diff/monsters_1/out-pure.nix @@ -0,0 +1,255 @@ +{ + # foo + stdenv, + # foo + # foo + lib, + # foo + # foo + fetchFromGitLab, + # foo + # foo + cairo, + # foo + # foo + desktop-file-utils, + # foo + # foo + gettext, + # foo + # foo + glib, + # foo + # foo + gtk4, + # foo + # foo + libadwaita, + # foo + # foo + meson, + # foo + # foo + ninja, + # foo + # foo + pango, + # foo + # foo + pkg-config, + # foo + # foo + python3, + # foo + # foo + rustPlatform, + # foo + # foo + wrapGAppsHook4, +# foo +}: +# foo +stdenv.mkDerivation + # foo + rec + # foo + { + # foo + pname + # foo + = + # foo + "contrast"; + # foo + version + # foo + = + # foo + "0.0.5"; + # foo + src + # foo + = + # foo + fetchFromGitLab + # foo + { + # foo + domain + # foo + = + # foo + "gitlab.gnome.org"; + # foo + group + # foo + = + # foo + "World"; + # foo + owner + # foo + = + # foo + "design"; + # foo + repo + # foo + = + # foo + "contrast"; + # foo + rev + # foo + = + # foo + version; + # foo + sha256 + # foo + = + # foo + "cypSbqLwSmauOoWOuppWpF3hvrxiqmkLspxAWzvlUC0="; + # foo + }; + # foo + cargoDeps + # foo + = + # foo + rustPlatform.fetchCargoTarball + # foo + { + # foo + inherit + # foo + src + ; + # foo + name + # foo + = + # foo + "${pname}-${version}"; + # foo + hash + # foo + = + # foo + "sha256-W4FyqwJpimf0isQRCq9TegpTQPQfsumx40AFQCFG5VQ="; + # foo + }; + # foo + nativeBuildInputs + # foo + = + # foo + [ + # foo + desktop-file-utils + # foo + gettext + # foo + meson + # foo + ninja + # foo + pkg-config + # foo + python3 + # foo + rustPlatform.rust.cargo + # foo + rustPlatform.cargoSetupHook + # foo + rustPlatform.rust.rustc + # foo + wrapGAppsHook4 + # foo + glib + # foo + # for glib-compile-resources + + # foo + ]; + # foo + buildInputs + # foo + = + # foo + [ + # foo + cairo + # foo + glib + # foo + gtk4 + # foo + libadwaita + # foo + pango + # foo + ]; + # foo + postPatch + # foo + = + # foo + '' + patchShebangs build-aux/meson_post_install.py + # https://gitlab.gnome.org/World/design/contrast/-/merge_requests/23 + substituteInPlace build-aux/meson_post_install.py \ + --replace "gtk-update-icon-cache" "gtk4-update-icon-cache" + ''; + # foo + meta + # foo + = + # foo + with + # foo + lib; + # foo + { + # foo + description + # foo + = + # foo + "Checks whether the contrast between two colors meet the WCAG requirements"; + # foo + homepage + # foo + = + # foo + "https://gitlab.gnome.org/World/design/contrast"; + # foo + license + # foo + = + # foo + licenses.gpl3Plus; + # foo + maintainers + # foo + = + # foo + with + # foo + maintainers; + # foo + [ + # foo + jtojnar + # foo + ]; + # foo + platforms + # foo + = + # foo + platforms.unix; + # foo + }; + # foo + } diff --git a/test/diff/monsters_2/out-pure.nix b/test/diff/monsters_2/out-pure.nix new file mode 100644 index 00000000..3051815f --- /dev/null +++ b/test/diff/monsters_2/out-pure.nix @@ -0,0 +1,31 @@ +{ + lib = { + + /* + Concatenate two lists + + Type: concat :: [a] -> [a] -> [a] + + Example: + concat [ 1 2 ] [ 3 4 ] + => [ 1 2 3 4 ] + */ + concat = x: y: x ++ y; + }; + + options = { + + boot.kernel.features = mkOption { + default = { }; + example = literalExpression "{ debug = true; }"; + internal = true; + description = '' + This option allows to enable or disable certain kernel features. + It's not API, because it's about kernel feature sets, that + make sense for specific use cases. Mostly along with programs, + which would have separate nixos options. + `grep features pkgs/os-specific/linux/kernel/common-config.nix` + ''; + }; + }; +} diff --git a/test/diff/monsters_3/out-pure.nix b/test/diff/monsters_3/out-pure.nix new file mode 100644 index 00000000..063dc219 --- /dev/null +++ b/test/diff/monsters_3/out-pure.nix @@ -0,0 +1,68 @@ +{ + stdenv, + lib, + fetchFromGitLab, + cairo, + desktop-file-utils, + gettext, + glib, + gtk4, + libadwaita, + meson, + ninja, + pango, + pkg-config, + python3, + rustPlatform, + wrapGAppsHook4, +}: +stdenv.mkDerivation rec { + pname = "contrast"; + version = "0.0.5"; + src = fetchFromGitLab { + domain = "gitlab.gnome.org"; + group = "World"; + owner = "design"; + repo = "contrast"; + rev = version; + sha256 = "cypSbqLwSmauOoWOuppWpF3hvrxiqmkLspxAWzvlUC0="; + }; + cargoDeps = rustPlatform.fetchCargoTarball { + inherit src; + name = "${pname}-${version}"; + hash = "sha256-W4FyqwJpimf0isQRCq9TegpTQPQfsumx40AFQCFG5VQ="; + }; + nativeBuildInputs = [ + desktop-file-utils + gettext + meson + ninja + pkg-config + python3 + rustPlatform.rust.cargo + rustPlatform.cargoSetupHook + rustPlatform.rust.rustc + wrapGAppsHook4 + glib # for glib-compile-resources + ]; + buildInputs = [ + cairo + glib + gtk4 + libadwaita + pango + ]; + postPatch = '' + patchShebangs build-aux/meson_post_install.py + # https://gitlab.gnome.org/World/design/contrast/-/merge_requests/23 + substituteInPlace build-aux/meson_post_install.py \ + --replace "gtk-update-icon-cache" "gtk4-update-icon-cache" + ''; + meta = with lib; { + description = "Checks whether the contrast between two colors meet the WCAG requirements"; + homepage = "https://gitlab.gnome.org/World/design/contrast"; + license = licenses.gpl3Plus; + maintainers = with maintainers; [ jtojnar ]; + platforms = platforms.unix; + }; +} diff --git a/test/diff/monsters_4/out-pure.nix b/test/diff/monsters_4/out-pure.nix new file mode 100644 index 00000000..ac311ac3 --- /dev/null +++ b/test/diff/monsters_4/out-pure.nix @@ -0,0 +1,146 @@ +# Foo +{ + stdenv # Foo + , # Foo + lib # Foo + , # Foo + fetchFromGitLab # Foo + , # Foo + cairo # Foo + , # Foo + desktop-file-utils # Foo + , # Foo + gettext # Foo + , # Foo + glib # Foo + , # Foo + gtk4 # Foo + , # Foo + libadwaita # Foo + , # Foo + meson # Foo + , # Foo + ninja # Foo + , # Foo + pango # Foo + , # Foo + pkg-config # Foo + , # Foo + python3 # Foo + , # Foo + rustPlatform # Foo + , # Foo + wrapGAppsHook4, # Foo +}: # Foo +stdenv.mkDerivation # Foo + rec # Foo + { + # Foo + pname # Foo + = # Foo + "contrast"; # Foo + version # Foo + = # Foo + "0.0.5"; # Foo + src # Foo + = # Foo + # Foo + fetchFromGitLab { + # Foo + domain # Foo + = # Foo + "gitlab.gnome.org"; # Foo + group # Foo + = # Foo + "World"; # Foo + owner # Foo + = # Foo + "design"; # Foo + repo # Foo + = # Foo + "contrast"; # Foo + rev # Foo + = # Foo + version; # Foo + sha256 # Foo + = # Foo + "cypSbqLwSmauOoWOuppWpF3hvrxiqmkLspxAWzvlUC0="; # Foo + }; # Foo + cargoDeps # Foo + = # Foo + rustPlatform.fetchCargoTarball # Foo + { + # Foo + inherit # Foo + src + ; # Foo + name # Foo + = # Foo + "${pname}-${version}"; # Foo + hash # Foo + = # Foo + "sha256-W4FyqwJpimf0isQRCq9TegpTQPQfsumx40AFQCFG5VQ="; # Foo + }; # Foo + nativeBuildInputs # Foo + = # Foo + [ + # Foo + desktop-file-utils # Foo + gettext # Foo + meson # Foo + ninja # Foo + pkg-config # Foo + python3 # Foo + rustPlatform.rust.cargo # Foo + rustPlatform.cargoSetupHook # Foo + rustPlatform.rust.rustc # Foo + wrapGAppsHook4 # Foo + glib # Foo for glib-compile-resources + # Foo + ]; # Foo + buildInputs # Foo + = # Foo + [ + # Foo + cairo # Foo + glib # Foo + gtk4 # Foo + libadwaita # Foo + pango # Foo + ]; # Foo + postPatch # Foo + = # Foo + '' + patchShebangs build-aux/meson_post_install.py + # https://gitlab.gnome.org/World/design/contrast/-/merge_requests/23 + substituteInPlace build-aux/meson_post_install.py \ + --replace "gtk-update-icon-cache" "gtk4-update-icon-cache" + ''; # Foo + meta # Foo + = # Foo + with # Foo + lib; # Foo + { + # Foo + description # Foo + = # Foo + "Checks whether the contrast between two colors meet the WCAG requirements"; # Foo + homepage # Foo + = # Foo + "https://gitlab.gnome.org/World/design/contrast"; # Foo + license # Foo + = # Foo + licenses.gpl3Plus; # Foo + maintainers # Foo + = # Foo + with # Foo + maintainers; # Foo + [ + # Foo + jtojnar # Foo + ]; # Foo + platforms # Foo + = # Foo + platforms.unix; # Foo + }; # Foo + } diff --git a/test/diff/monsters_5/out-pure.nix b/test/diff/monsters_5/out-pure.nix new file mode 100644 index 00000000..f7a798a2 --- /dev/null +++ b/test/diff/monsters_5/out-pure.nix @@ -0,0 +1,273 @@ +{ + + config, + + lib, + + pkgs, + + ... + +}: + +with + + lib; + +let + + inherit + + (config.boot) + + kernelPatches + ; + + inherit + + (config.boot.kernel) + + features + + randstructSeed + ; + + inherit + + (config.boot.kernelPackages) + + kernel + ; + + kernelModulesConf + + = + + pkgs.writeText + + "nixos.conf" + + '' + ${concatStringsSep "\n" config.boot.kernelModules} + ''; + +in + +{ + + ###### interface + + options + + = + + { + + boot.kernel.features + + = + + mkOption + + { + + default + + = + + { }; + + example + + = + + literalExpression + + "{debug= true;}"; + + internal + + = + + true; + + description + + = + + '' + This option allows to enable or disable certain kernel features. + It's not API, because it's about kernel feature sets, that + make sense for specific use cases. Mostly along with programs, + which would have separate nixos options. + `grep features pkgs/os-specific/linux/kernel/common-config.nix` + ''; + + }; + + boot.kernelPackages + + = + + mkOption + + { + + default + + = + + pkgs.linuxPackages; + + type + + = + + types.unspecified + + // + + { + + merge + + = + + mergeEqualOption; + + }; + + apply + + = + + kernelPackages: + + kernelPackages.extend + + ( + self: + + super: + + { + + kernel + + = + + super.kernel.override + + ( + originalArgs: + + { + + inherit + + randstructSeed + ; + + kernelPatches + + = + + (originalArgs.kernelPatches + + or + + [ ] + ) + + ++ + + kernelPatches; + + features + + = + + lib.recursiveUpdate + + super.kernel.features + + features; + + } + ); + + } + ); + + # We don't want to evaluate all of linuxPackages for the manual + # - some of it might not even evaluate correctly. + + defaultText + + = + + literalExpression + + "pkgs.linuxPackages"; + + example + + = + + literalExpression + + "pkgs.linuxKernel.packages.linux_5_10"; + + description + + = + + '' + This option allows you to override the Linux kernel used by + NixOS. Since things like external kernel module packages are + tied to the kernel you're using, it also overrides those. + This option is a function that takes Nixpkgs as an argument + (as a convenience), and returns an attribute set containing at + the very least an attribute kernel. + Additional attributes may be needed depending on your + configuration. For instance, if you use the NVIDIA X driver, + then it also needs to contain an attribute + nvidia_x11. + ''; + + }; + + boot.kernelPatches + + = + + mkOption + + { + + type + + = + + types.listOf + + types.attrs; + + default + + = + + [ ]; + + example + + = + + literalExpression + + "[ pkgs.kernelPatches.ubuntu_fan_4_4 ]"; + description = "A list of additional patches to apply to the kernel."; + }; + + }; +} diff --git a/test/diff/operation/out-pure.nix b/test/diff/operation/out-pure.nix new file mode 100644 index 00000000..f032b244 --- /dev/null +++ b/test/diff/operation/out-pure.nix @@ -0,0 +1,289 @@ +[ + ( + # To find infinite recursion in NixOS option docs: + # builtins.trace opt.loc + [ docOption ] ++ optionals subOptionsVisible subOptions + ) + ( + # Filter out git + baseName == ".gitignore" + || (type == "directory" && baseName == ".git") + || ( + type == "directory" + && ( + baseName == "target" + || baseName == "_site" + || baseName == ".sass-cache" + || baseName == ".jekyll-metadata" + || baseName == "build-artifacts" + ) + ) + || (type == "symlink" && lib.hasPrefix "result" baseName) + || (type == "directory" && (baseName == ".idea" || baseName == ".vscode")) + || lib.hasSuffix ".iml" baseName + # some other comment + || baseName == "Cargo.nix" + || lib.hasSuffix "~" baseName + || builtins.match "^\\.sw[a-z]$$" baseName != null + # a third comment + || builtins.match "^\\..*\\.sw[a-z]$$" baseName != null + || lib.hasSuffix ".tmp" baseName + || + # fourth comment + lib.hasSuffix ".bak" baseName + || + # fifth comment + baseName == "tests.nix" + # comment on operator inside + || baseName == "tests.nix" + # comment absorbable term + || { } + # comment absorbable term 2 + || { + foo = "bar"; # multiline + } + # comment on function application + || foo bar baz + # comment on function application 2 + || foo bar baz [ + 1 + 2 + ] + # comment on other + || foo ? bar + ) + # Filter out nix-build result symlinks + (type == "symlink" && lib.hasPrefix "result" baseName) + ( + # Filter out nix-build result symlinks + (type == "symlink" && lib.hasPrefix "result" baseName) + # Filter out sockets and other types of files we can't have in the store. + || (type == "unknown") + || + # Filter out sockets and other types of files we can't have in the store. + (type == "unknown") + # Filter out sockets and other types of files we can't have in the store. + || (type == "unknown") + ) + ( + # Don't bother wrapping unless we actually have plugins, since the wrapper will stop automatic downloading + # of plugins, which might be counterintuitive if someone just wants a vanilla Terraform. + if actualPlugins == [ ] then + terraform.overrideAttrs (orig: { + passthru = orig.passthru // passthru; + }) + else + lib.appendToName "with-plugins" ( + stdenv.mkDerivation { + inherit (terraform) meta pname version; + nativeBuildInputs = [ makeWrapper ]; + } + ) + ) + ( + if + (cpu.family == "arm" && cpu.bits == 32) + || (cpu.family == "sparc" && cpu.bits == 32) + || (cpu.family == "m68k" && cpu.bits == 32) + || (cpu.family == "x86" && cpu.bits == 32) + then + execFormats.aout + else + execFormats.elf + ) + ( + [ + aaaaaaaaaaaaa + aaaaaaaaaaaaa + ] + + + [ + bbbbbbbbbbbbbb + bbbbbbbbbbbbbbb + ] + * [ + ccccccccccccccc + ccccccccccccccccccc + ] + ) + ( + [ + aaaaaaaaaaaaa + aaaaaaaaaaaaa + ] + * [ + bbbbbbbbbbbbbb + bbbbbbbbbbbbbbb + ] + + [ + ccccccccccccccc + ccccccccccccccccccc + ] + ) + + ( + [ + 1 + 2 + 3 + ] + / [ + 4 + 5 + 6 + ] + / [ + 7 + 8 + 9 + ] + ) + ( + [ + 1 + 2 + 3 + ] + ++ [ + 4 + 5 + 6 + ] + ++ [ + 7 + 8 + 9 + ] + ) + + ( + [ + some + flags # multiline + ] + ++ [ short ] + ++ [ + more + stuff # multiline + ] + ++ (if foo then [ bar ] else [ baz ]) + ++ [ ] + ++ (optionals condition [ + more + items + ]) + ) + + # Test precedence + ( + aaaaaaaaaaaaaaa + + bbbbbbbbbbbbbbbbbbbb + + ccccccccccccccccccccccccccc + + ddddddddddddddddddddddd * eeeeeeeeeeeeeeeeeeeeeeee + + + ffffffffffffffffffffffffff + * + gggggggggggggggggggggggg + ++ hhhhhhhhhhhhhhhhhhhhhhhhhhh + ++ iiiiiiiiiiiiiiiiiiiiiiiiiiiiiiii + * jjjjjjjjjjjjjjjjjjjjj + ) + + # Logical precedence + ( + assert pipewireSupport -> !waylandSupport || !webrtcSupport -> pipewireSupport; + if + aaaaaaaaaaaaaa && bbbbbbbbbbbb + || cccccccccccccccccccc && ddddddddddddddddd + || eeeeeeeeeeeeeeeeeeee && fffffffffffffffffffffffffff + then + [ ] + else if + aaaaaaaaaaaaaaaaaaaaa + || bbbbbbbbbbbbbbbbbbb && cccccccccccccccccccccccccccccccc + || ddddddddddddddddd && eeeeeeeeeeeeeeeeeeee + || fffffffffffffffffffffffffff + then + [ ] + else if + aaaaaaaaaaaaaa && bbbbbbbbbbbb && aaaaaaaaaaaaaa && bbbbbbbbbbbb + || + cccccccccccccccccccc + && ddddddddddddddddd + && cccccccccccccccccccc + && ddddddddddddddddd + || + eeeeeeeeeeeeeeeeeeee + && fffffffffffffffffffffffffff + && eeeeeeeeeeeeeeeeeeee + && fffffffffffffffffffffffffff + then + [ ] + else + { } + ) + + # Indentation + ( + [ + #multiline + zip + zlib + ] + ++ [ (if (lib.versionAtLeast version "103") then nss_latest else nss_esr) ] + ) + + # Indentation with parenthesized multiline function call + ( + [ + 1 + 2 + 3 + ] + ++ (isOneOf item [ + 1 + 2 + 3 + 4 + ]) + ++ isOneOf item [ + 1 + 2 + 3 + 4 + ] + ) + # Interaction with function calls + ( + g { + # multiline + y = 20; + } + * f { + # multiline + x = 10; + } + + + g { + # multiline + y = 20; + } + * h { + # multiline + z = 30; + } + ) + + # Experimental pipe operators + ( + a // b + |> f "very long argument should justify splitting this over multiple lines" + |> g { } + ) + + ( + g { } + <| f "very long argument should justify splitting this over multiple lines" + <| a // b + ) +] diff --git a/test/diff/operation/out.nix b/test/diff/operation/out.nix index f032b244..3e1759f4 100644 --- a/test/diff/operation/out.nix +++ b/test/diff/operation/out.nix @@ -230,7 +230,9 @@ zip zlib ] - ++ [ (if (lib.versionAtLeast version "103") then nss_latest else nss_esr) ] + ++ [ + (if (lib.versionAtLeast version "103") then nss_latest else nss_esr) + ] ) # Indentation with parenthesized multiline function call diff --git a/test/diff/operator-after-operator/out-pure.nix b/test/diff/operator-after-operator/out-pure.nix new file mode 100644 index 00000000..34bf728a --- /dev/null +++ b/test/diff/operator-after-operator/out-pure.nix @@ -0,0 +1,2 @@ +# https://github.com/NixOS/nixfmt/issues/122 +(1 + 1) (1 + 0.4) diff --git a/test/diff/or_default/out-pure.nix b/test/diff/or_default/out-pure.nix new file mode 100644 index 00000000..67abd48c --- /dev/null +++ b/test/diff/or_default/out-pure.nix @@ -0,0 +1,17 @@ +[ + (a.b or c) + (a.b or c) + (a.b or c) + (a.b or c) + (a.b or (a.b or (a.b or c))) + (a.b or (a.b or (a.b or c))) + (a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a + or a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a + ) + (a.a or a.a # test + or a.a # test + or # test + a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a or a.a + or a.a or a.a or a.a or a.a or a.a + ) +] diff --git a/test/diff/paren/out-pure.nix b/test/diff/paren/out-pure.nix new file mode 100644 index 00000000..ae628d76 --- /dev/null +++ b/test/diff/paren/out-pure.nix @@ -0,0 +1,94 @@ +[ + ( + done + // listToAttrs [ + { + # multline + name = entry; + value = 1; + } + ] + ) +] + ( + ( + # test + a # test + ) + ((c)) + ( + (c) # e + ) + ( + ( + c # d + ) + ) + ( + ( + c # d + ) # e + ) + ( + # b + (c) + ) + ( + # b + (c) # e + ) + ( + # b + ( + c # d + ) + ) + ( + # b + ( + c # d + ) # e + ) + # a + ((c)) + # a + ( + (c) # e + ) + # a + ( + ( + c # d + ) + ) + # a + ( + ( + c # d + ) # e + ) + # a + ( + # b + (c) + ) + # a + ( + # b + (c) # e + ) + # a + ( + # b + ( + c # d + ) + ) + ( + # a + # b + ( + c # d + ) # e + ) + ) diff --git a/test/diff/pat_bind/out-pure.nix b/test/diff/pat_bind/out-pure.nix new file mode 100644 index 00000000..7105a893 --- /dev/null +++ b/test/diff/pat_bind/out-pure.nix @@ -0,0 +1,11 @@ +[ + ({ }@a: _) + ({ }@a: _) + ({ }@a: _) + ({ }@a: _) + + (a@{ }: _) + (a@{ }: _) + (a@{ }: _) + (a@{ }: _) +] diff --git a/test/diff/pattern/out-pure.nix b/test/diff/pattern/out-pure.nix new file mode 100644 index 00000000..cdac106f --- /dev/null +++ b/test/diff/pattern/out-pure.nix @@ -0,0 +1,696 @@ +[ + ( + { + foo, + bar, + # Some comment + baz, + }: + { } + ) + ( + { + foo, + bar, # Some comment + baz, # More comment + }: + { } + ) + ( + { + foo, + bar, + # Some comment + baz, + }: + { } + ) + ( + { + foo, + bar, # Some comment + }: + { } + ) + ( + a@{ + self, + gomod2nix, + mach-nix, + }: + _ + ) + ( + { + self, + gomod2nix, + mach-nix, + }@inp: + _ + ) + ( + { + a ? [ + 1 + 2 + 3 + ], + b ? { + # ... + }, + }: + _ + ) + ({ }: _) + ({ a }: _) + ({ }: _) + ({ ... }: _) + ({ ... }: _) + ({ ... }: _) + ({ ... }: _) + + ({ b, e, ... }: _) + ( + { + b, + e, + ... # h + }: + _ + ) + ( + { + b, + e, # g + ... + }: + _ + ) + ( + { + b, + e, # g + ... # h + }: + _ + ) + ( + { + b, + e, # f + ... + }: + _ + ) + ( + { + b, + e, # f + ... # h + }: + _ + ) + ( + { + b, + e # f + , # g + ... + }: + _ + ) + ( + { + b, + e # f + , # g + ... # h + }: + _ + ) + ( + { + b, # d + e, + ... + }: + _ + ) + ( + { + b, # d + e, + ... # h + }: + _ + ) + ( + { + b, # d + e, # g + ... + }: + _ + ) + ( + { + b, # d + e, # g + ... # h + }: + _ + ) + ( + { + b, # d + e, # f + ... + }: + _ + ) + ( + { + b, # d + e, # f + ... # h + }: + _ + ) + ( + { + b, # d + e # f + , # g + ... + }: + _ + ) + ( + { + b, # d + e # f + , # g + ... # h + }: + _ + ) + ( + { + b, # c + e, + ... + }: + _ + ) + ( + { + b, # c + e, + ... # h + }: + _ + ) + ( + { + b, # c + e, # g + ... + }: + _ + ) + ( + { + b, # c + e, # g + ... # h + }: + _ + ) + ( + { + b, # c + e, # f + ... + }: + _ + ) + ( + { + b, # c + e, # f + ... # h + }: + _ + ) + ( + { + b, # c + e # f + , # g + ... + }: + _ + ) + ( + { + b, # c + e # f + , # g + ... # h + }: + _ + ) + ( + { + b # c + , # d + e, + ... + }: + _ + ) + ( + { + b # c + , # d + e, + ... # h + }: + _ + ) + ( + { + b # c + , # d + e, # g + ... + }: + _ + ) + ( + { + b # c + , # d + e, # g + ... # h + }: + _ + ) + ( + { + b # c + , # d + e, # f + ... + }: + _ + ) + ( + { + b # c + , # d + e, # f + ... # h + }: + _ + ) + ( + { + b # c + , # d + e # f + , # g + ... + }: + _ + ) + ( + { + b # c + , # d + e # f + , # g + ... # h + }: + _ + ) + ( + # a + { b, e, ... }: _ + ) + ( + # a + { + b, + e, + ... # h + }: + _ + ) + ( + # a + { + b, + e, # g + ... + }: + _ + ) + ( + # a + { + b, + e, # g + ... # h + }: + _ + ) + ( + # a + { + b, + e, # f + ... + }: + _ + ) + ( + # a + { + b, + e, # f + ... # h + }: + _ + ) + ( + # a + { + b, + e # f + , # g + ... + }: + _ + ) + ( + # a + { + b, + e # f + , # g + ... # h + }: + _ + ) + ( + # a + { + b, # d + e, + ... + }: + _ + ) + ( + # a + { + b, # d + e, + ... # h + }: + _ + ) + ( + # a + { + b, # d + e, # g + ... + }: + _ + ) + ( + # a + { + b, # d + e, # g + ... # h + }: + _ + ) + ( + # a + { + b, # d + e, # f + ... + }: + _ + ) + ( + # a + { + b, # d + e, # f + ... # h + }: + _ + ) + ( + # a + { + b, # d + e # f + , # g + ... + }: + _ + ) + ( + # a + { + b, # d + e # f + , # g + ... # h + }: + _ + ) + ( + # a + { + b, # c + e, + ... + }: + _ + ) + ( + # a + { + b, # c + e, + ... # h + }: + _ + ) + ( + # a + { + b, # c + e, # g + ... + }: + _ + ) + ( + # a + { + b, # c + e, # g + ... # h + }: + _ + ) + ( + # a + { + b, # c + e, # f + ... + }: + _ + ) + ( + # a + { + b, # c + e, # f + ... # h + }: + _ + ) + ( + # a + { + b, # c + e # f + , # g + ... + }: + _ + ) + ( + # a + { + b, # c + e # f + , # g + ... # h + }: + _ + ) + ( + # a + { + b # c + , # d + e, + ... + }: + _ + ) + ( + # a + { + b # c + , # d + e, + ... # h + }: + _ + ) + ( + # a + { + b # c + , # d + e, # g + ... + }: + _ + ) + ( + # a + { + b # c + , # d + e, # g + ... # h + }: + _ + ) + ( + # a + { + b # c + , # d + e, # f + ... + }: + _ + ) + ( + # a + { + b # c + , # d + e, # f + ... # h + }: + _ + ) + ( + # a + { + b # c + , # d + e # f + , # g + ... + }: + _ + ) + ( + # a + { + b # c + , # d + e # f + , # g + ... # h + }: + _ + ) + + ( + { + a ? null, + }: + _ + ) + ( + # a + { + b # a + ? # a + null # c + , # d + e # a + ? # a + null # f + , # g + ... # h + }: + _ + ) + + ( + { + # a + # + b + # a + # + ? + # a + # + null, + # c + # + # d + # + e + # a + # + ? + # a + # + null, + # f + # + # g + # + ... + # h + # + } + # i + # + : + # j + # + _ + ) +] diff --git a/test/diff/regression-218/out-pure.nix b/test/diff/regression-218/out-pure.nix new file mode 100644 index 00000000..001d48e5 --- /dev/null +++ b/test/diff/regression-218/out-pure.nix @@ -0,0 +1,6 @@ +{ + foo, + # bar + baz, # qux +}: +null diff --git a/test/diff/root/out-pure.nix b/test/diff/root/out-pure.nix new file mode 100644 index 00000000..12820fc5 --- /dev/null +++ b/test/diff/root/out-pure.nix @@ -0,0 +1,12 @@ +/* + Some functions f + name attribute. +*/ +/* + Add to or over + derivation. + + Example: + addMetaAttrs {des +*/ +1 diff --git a/test/diff/select/out-pure.nix b/test/diff/select/out-pure.nix new file mode 100644 index 00000000..4248fbcb --- /dev/null +++ b/test/diff/select/out-pure.nix @@ -0,0 +1,15 @@ +[ + (a.a) + (a.a) + (a.a) + (a.a) + (a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a) + (a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a.a) + ( + { + # multiple lines + foo = "bar"; + } + .a.b.c + ) +] diff --git a/test/diff/string/out-pure.nix b/test/diff/string/out-pure.nix new file mode 100644 index 00000000..f5d1ebca --- /dev/null +++ b/test/diff/string/out-pure.nix @@ -0,0 +1,95 @@ +[ + '' + foo +  bar + '' + "" + ### + " + " + ### + "a + ${x} + b + " + ### + '''' + ### + ''a'' + ### + ''${""}'' + ### + '' + ${""} + + '' + ### + '' + a + '' + ### + '' + a + + '' + ### + '' + a + '' + ### + + '' + a + '' + ### + '' + a + ${""} + b + ${""} + c ${""} d + e + '' + ### + '''' + ### + '' + declare -a makefiles=(./*.mak) + sed -i -f ${makefile-sed} "''${makefiles[@]}" + ### assign Makefile variables eagerly & change backticks to `$(shell …)` + sed -i -e 's/ = `\([^`]\+\)`/ := $(shell \1)/' \ + -e 's/`\([^`]\+\)`/$(shell \1)/' \ + "''${makefiles[@]}" + '' + ### + '' + [${mkSectionName sectName}] + '' + ### + ''-couch_ini ${cfg.package}/etc/default.ini ${configFile} ${pkgs.writeText "couchdb-extra.ini" cfg.extraConfig} ${cfg.configFile}'' + ### + ''exec i3-input -F "mark %s" -l 1 -P 'Mark: ' '' + ### + ''exec i3-input -F '[con_mark="%s"] focus' -l 1 -P 'Go to: ' '' + ### + ''"${pkgs.name or ""}";'' + ### + ''${pkgs.replace-secret}/bin/replace-secret '${placeholder}' '${secretFile}' '${targetFile}' '' + ### + '' + mkdir -p "$out/lib/modules/${kernel.modDirVersion}/kernel/net/wireless/" + '' + ### + '' + + + + ${expr "" v} + '' + + '' + --${"test"} + '' + + "--${"test"}" +] diff --git a/test/diff/string_interpol/out-pure.nix b/test/diff/string_interpol/out-pure.nix new file mode 100644 index 00000000..643949e4 --- /dev/null +++ b/test/diff/string_interpol/out-pure.nix @@ -0,0 +1,95 @@ +[ + "${ + # a + "${ + # b + "${c}" + }" # d + }" + ''${ + # a + ''${ + # b + ''${c}'' + }'' # d + }'' + { + ExecStart = "${pkgs.openarena}/bin/oa_ded +set fs_basepath ${pkgs.openarena}/openarena-0.8.8 +set fs_homepath /var/lib/openarena ${ + concatMapStringsSep (x: x) " " cfg.extraFlags + }"; + description = "${ + optionDescriptionPhrase (class: class == "noun" || class == "conjunction") t1 + } or ${ + optionDescriptionPhrase ( + class: class == "noun" || class == "conjunction" || class == "composite" + ) t2 + }"; + ruleset = '' + table ip nat { + chain port_redirects { + type nat hook prerouting priority dstnat + policy accept + + ${ + builtins.concatStringsSep "\n" ( + map ( + e: + "iifname \"${cfg.upstreamIface}\" tcp dport ${builtins.toString e.sourcePort} dnat to ${e.destination}" + ) tcpPortMap + ) + } + + ${ + builtins.concatStringsSep "\n" ( + map ( + e: + "ifname \"${cfg.upstreamIface}\" udp dport ${builtins.toString e.sourcePort} dnat to ${e.destination}" + ) udpPortMap + ) + } + } + ''; + } + { + system.nixos.versionSuffix1 = ".${ + final.substring 0 8 ( + self.lastModifiedDate or self.lastModified or "19700101" + self.lastModifiedDate or self.lastModified or "19700101" + ) + }.${self.shortRev or "dirty"}"; + + system.nixos.versionSuffix2 = ".${ + final.substring 0 8 ( + self.lastModifiedDate or self.lastModified or "19700101" + self.lastModifiedDate or self.lastModified or "19700101" + ) + }"; + + system.nixos.versionSuffix3 = "${final.substring 0 8 ( + self.lastModifiedDate or self.lastModified or "19700101" + self.lastModifiedDate or self.lastModified or "19700101" + )}"; + } + (system nixos versionSuffix1 + ".${ + final.substring 0 8 ( + self.lastModifiedDate or self.lastModified or "19700101" + self.lastModifiedDate or self.lastModified or "19700101" + ) + }.${self.shortRev or "dirty"}" + ) + (system nixos versionSuffix2 + ".${ + final.substring 0 8 ( + self.lastModifiedDate or self.lastModified or "19700101" + self.lastModifiedDate or self.lastModified or "19700101" + ) + }" + ) + (system nixos versionSuffix3 + "${final.substring 0 8 ( + self.lastModifiedDate or self.lastModified or "19700101" + self.lastModifiedDate or self.lastModified or "19700101" + )}" + ) +] diff --git a/test/diff/with/out-pure.nix b/test/diff/with/out-pure.nix new file mode 100644 index 00000000..9c71920b --- /dev/null +++ b/test/diff/with/out-pure.nix @@ -0,0 +1,155 @@ +[ + (with b; c) + ( + with b; # b + c + ) + ( + with # a + b; + c + ) + ( + with # a + b; # b + c + ) + (with b; cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc) + (with b; cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc) + { a = with b; 1; } + { a = with b; 1 + 1; } + { + a = with b; { + c = 1; + }; + } + { + a = with b; { + c = 1; + d = 2; + e = 3; + }; + } + { + a = + with b; # comment + [ + 1 + 2 + 3 + ]; + } + { + a = + with b; + # comment + 1; + } + { + a = with b; 1; + # comment + } + ([ 1 ]) + (with a; [ 1 ]) + ([ + 1 + 2 + 3 + ]) + (with a; [ + 1 + 2 + 3 + ]) + (with a; with b; with c; [ 1 ]) + (with a; with b; with c; { a = 1; }) + ( + with a; # comment + with b; + with c; + { + a = 1; + } + ) + ( + with a; + with b; + with c; + { + a = 1; + b = 2; + } + ) + ( + with a; # comment + with b; + with c; + { + a = 1; + b = 2; + } + ) + { a = with b; with b; with b; 1; } + { + binPath = + with pkgs; + makeBinPath ([ + rsync + util-linux + ]); + } + (with a; { }) + (with a; [ + 1 + 2 + 3 + ]) + (with a; if null then true else false) + ( + with a; + let + in + [ + 1 + 2 + 3 + ] + ) + ( + { + gst_plugins ? with gst_all_1; [ + gst-plugins-good + gst-plugins-ugly + ], + more ? + with stuff; + let + in + [ + 1 + 2 + 3 + ], + things ? with a; if null then true else false, + things ? + with a; + if null then true else "looooooooooooooooooooooooooooooooooooong", + }: + { } + ) + { + more = + with stuff; + let + in + [ + 1 + 2 + 3 + ]; + things = with a; if null then true else false; + things = + with a; + if null then true else "looooooooooooooooooooooooooooooooooooong"; + } +] diff --git a/test/diff/with/out.nix b/test/diff/with/out.nix index 9c71920b..dbaea7e0 100644 --- a/test/diff/with/out.nix +++ b/test/diff/with/out.nix @@ -89,7 +89,9 @@ b = 2; } ) - { a = with b; with b; with b; 1; } + { + a = with b; with b; with b; 1; + } { binPath = with pkgs; diff --git a/test/test.sh b/test/test.sh index 4a28ed19..6ba2e70c 100755 --- a/test/test.sh +++ b/test/test.sh @@ -26,7 +26,7 @@ nixfmt --version # Verify "correct", files that don't change when formatted for file in test/correct/*.nix; do echo "Checking $file …" - if ! out=$(nixfmt --verify < "$file"); then + if ! out=$(nixfmt --strict --verify < "$file"); then echo "[ERROR] failed nixfmt verification" exit 1 fi @@ -54,10 +54,23 @@ done # Verify "diff" for file in test/diff/**/in.nix; do - outfile="$(dirname "$file")/out.nix" - echo "Checking $file …" out="$(nixfmt --verify < "$file")" + outfile="$(dirname "$file")/out.nix" + + if diff --color=always --unified "$outfile" <(echo "$out"); then + echo "[OK]" + elif [[ $* == *--update-diff* ]]; then + echo "$out" > "$outfile" + echo "[UPDATED] $outfile" + else + echo "[ERROR] (run with --update-diff to update the diff)" + exit 1 + fi + + echo "Checking $file with --strict …" + out="$(nixfmt --strict --verify < "$file")" + outfile="$(dirname "$file")/out-pure.nix" if diff --color=always --unified "$outfile" <(echo "$out"); then echo "[OK]"