diff --git a/benchmarks/ParserBench.hs b/benchmarks/ParserBench.hs index fd5df974e..d1755c6ee 100644 --- a/benchmarks/ParserBench.hs +++ b/benchmarks/ParserBench.hs @@ -2,20 +2,20 @@ module ParserBench (benchmarks) where import Nix.Parser -import Control.Applicative import Criterion benchFile :: FilePath -> Benchmark -benchFile = bench <*> whnfIO . parseNixFile . ("data/" ++) +benchFile = bench <*> whnfIO . parseNixFile . ("data/" <>) benchmarks :: Benchmark benchmarks = bgroup - "Parser" - [ benchFile "nixpkgs-all-packages.nix" - , benchFile "nixpkgs-all-packages-pretty.nix" - , benchFile "let-comments.nix" - , benchFile "let-comments-multiline.nix" - , benchFile "let.nix" - , benchFile "simple.nix" - , benchFile "simple-pretty.nix" - ] + "Parser" $ + fmap benchFile + [ "nixpkgs-all-packages.nix" + , "nixpkgs-all-packages-pretty.nix" + , "let-comments.nix" + , "let-comments-multiline.nix" + , "let.nix" + , "simple.nix" + , "simple-pretty.nix" + ] diff --git a/main/Main.hs b/main/Main.hs index 78a3d1822..048a64110 100644 --- a/main/Main.hs +++ b/main/Main.hs @@ -143,13 +143,13 @@ main = do = liftIO . putStrLn . Text.unpack - . principledStringIgnoreContext + . stringIgnoreContext . toXML <=< normalForm | json opts = liftIO . Text.putStrLn - . principledStringIgnoreContext + . stringIgnoreContext <=< nvalueToJSONNixString | strict opts = liftIO . print . prettyNValue <=< normalForm diff --git a/src/Nix/Builtins.hs b/src/Nix/Builtins.hs index a7e8d8eb1..bf36761a5 100644 --- a/src/Nix/Builtins.hs +++ b/src/Nix/Builtins.hs @@ -76,14 +76,15 @@ import Nix.Options import Nix.Parser hiding ( nixPath ) import Nix.Render import Nix.Scope -import Nix.String +import Nix.String hiding (getContext) +import qualified Nix.String as NixString import Nix.String.Coerce import Nix.Utils import Nix.Value import Nix.Value.Equal import Nix.Value.Monad import Nix.XML -import System.Nix.Base32 as Base32 +import System.Nix.Base32 as Base32 import System.FilePath import System.Posix.Files ( isRegularFile , isDirectory @@ -104,7 +105,7 @@ withNixContext mpath action = do opts :: Options <- asks (view hasLens) let i = nvList $ map ( nvStr - . hackyMakeNixStringWithoutContext + . makeNixStringWithoutContext . Text.pack ) (include opts) @@ -140,7 +141,7 @@ data Builtin v = Builtin builtinsList :: forall e t f m . MonadNix e t f m => m [Builtin (NValue t f m)] builtinsList = sequence [ do - version <- toValue (principledMakeNixStringWithoutContext "2.3") + version <- toValue (makeNixStringWithoutContext "2.3") pure $ Builtin Normal ("nixVersion", version) , do version <- toValue (5 :: Int) @@ -163,7 +164,7 @@ builtinsList = sequence , add2 Normal "compareVersions" compareVersions_ , add Normal "concatLists" concatLists , add2 Normal "concatMap" concatMap_ - , add' Normal "concatStringsSep" (arity2 principledIntercalateNixString) + , add' Normal "concatStringsSep" (arity2 intercalateNixString) , add0 Normal "currentSystem" currentSystem , add0 Normal "currentTime" currentTime_ , add2 Normal "deepSeq" deepSeq @@ -260,9 +261,9 @@ builtinsList = sequence , add2 Normal "sort" sort_ , add2 Normal "split" split_ , add Normal "splitVersion" splitVersion_ - , add0 Normal "storeDir" (pure $ nvStr $ principledMakeNixStringWithoutContext "/nix/store") + , add0 Normal "storeDir" (pure $ nvStr $ makeNixStringWithoutContext "/nix/store") --, add Normal "storePath" storePath - , add' Normal "stringLength" (arity1 $ Text.length . principledStringIgnoreContext) + , add' Normal "stringLength" (arity1 $ Text.length . stringIgnoreContext) , add' Normal "sub" (arity2 ((-) @Integer)) , add' Normal "substring" substring , add Normal "tail" tail_ @@ -320,7 +321,7 @@ foldNixPath f z = do mDataDir <- getEnvVar "NIX_DATA_DIR" dataDir <- maybe getDataDir pure mDataDir foldrM go z - $ map (fromInclude . principledStringIgnoreContext) dirs + $ map (fromInclude . stringIgnoreContext) dirs ++ case mPath of Nothing -> [] Just str -> uriAwareSplit (Text.pack str) @@ -341,12 +342,12 @@ nixPath = fmap nvList $ flip foldNixPath [] $ \p mn ty rest -> PathEntryPath -> ("path", nvPath p) PathEntryURI -> ( "uri" - , nvStr $ hackyMakeNixStringWithoutContext $ Text.pack p + , nvStr $ makeNixStringWithoutContext $ Text.pack p ) , ( "prefix" , nvStr - $ hackyMakeNixStringWithoutContext $ Text.pack $ fromMaybe "" mn + $ makeNixStringWithoutContext $ Text.pack $ fromMaybe "" mn ) ] ) @@ -392,7 +393,7 @@ unsafeGetAttrPos -> m (NValue t f m) unsafeGetAttrPos x y = demand x $ \x' -> demand y $ \y' -> case (x', y') of (NVStr ns, NVSet _ apos) -> - case M.lookup (hackyStringIgnoreContext ns) apos of + case M.lookup (stringIgnoreContext ns) apos of Nothing -> pure $ nvConstant NNull Just delta -> toValue delta (x, y) -> @@ -538,7 +539,7 @@ splitVersion_ = fromValue >=> fromStringNoContext >=> \s -> $ nvList $ flip map (splitVersion s) $ nvStr - . principledMakeNixStringWithoutContext + . makeNixStringWithoutContext . versionComponentToString compareVersions :: Text -> Text -> Ordering @@ -585,10 +586,10 @@ parseDrvName = fromValue >=> fromStringNoContext >=> \s -> do let (name :: Text, version :: Text) = splitDrvName s toValue @(AttrSet (NValue t f m)) $ M.fromList [ ( "name" :: Text - , nvStr $ principledMakeNixStringWithoutContext name + , nvStr $ makeNixStringWithoutContext name ) , ( "version" - , nvStr $ principledMakeNixStringWithoutContext version + , nvStr $ makeNixStringWithoutContext version ) ] @@ -604,13 +605,13 @@ match_ pat str = fromValue pat >>= fromStringNoContext >>= \p -> -- context of its second argument. This is probably a bug but we're -- going to preserve the behavior here until it is fixed upstream. -- Relevant issue: https://github.com/NixOS/nix/issues/2547 - let s = principledStringIgnoreContext ns + let s = stringIgnoreContext ns let re = makeRegex (encodeUtf8 p) :: Regex let mkMatch t | Text.null t = toValue () | -- Shorthand for Null - otherwise = toValue $ principledMakeNixStringWithoutContext t + otherwise = toValue $ makeNixStringWithoutContext t case matchOnceText re (encodeUtf8 s) of Just ("", sarr, "") -> do let s = map fst (elems sarr) @@ -630,7 +631,7 @@ split_ pat str = fromValue pat >>= fromStringNoContext >>= \p -> -- context of its second argument. This is probably a bug but we're -- going to preserve the behavior here until it is fixed upstream. -- Relevant issue: https://github.com/NixOS/nix/issues/2547 - let s = principledStringIgnoreContext ns + let s = stringIgnoreContext ns let re = makeRegex (encodeUtf8 p) :: Regex haystack = encodeUtf8 s pure $ nvList $ splitMatches 0 @@ -657,13 +658,13 @@ splitMatches numDropped (((_, (start, len)) : captures) : mts) haystack = caps = nvList (map f captures) f (a, (s, _)) = if s < 0 then nvConstant NNull else thunkStr a -thunkStr s = nvStr (hackyMakeNixStringWithoutContext (decodeUtf8 s)) +thunkStr s = nvStr (makeNixStringWithoutContext (decodeUtf8 s)) substring :: forall e t f m. MonadNix e t f m => Int -> Int -> NixString -> Prim m NixString substring start len str = Prim $ if start < 0 then throwError $ ErrorCall $ "builtins.substring: negative start position: " ++ show start - else pure $ principledModifyNixContents (take . Text.drop start) str + else pure $ modifyNixContents (take . Text.drop start) str where --NOTE: negative values of 'len' are OK, and mean "take everything" take = if len < 0 then id else Text.take len @@ -674,7 +675,7 @@ attrNames = fromValue @(AttrSet (NValue t f m)) >=> fmap getDeeper . toValue - . map principledMakeNixStringWithoutContext + . map makeNixStringWithoutContext . sort . M.keys @@ -714,7 +715,7 @@ mapAttrs_ f xs = fromValue @(AttrSet (NValue t f m)) xs >>= \aset -> do defer @(NValue t f m) $ withFrame Debug (ErrorCall "While applying f in mapAttrs:\n") $ callFunc ?? value - =<< callFunc f (nvStr (principledMakeNixStringWithoutContext key)) + =<< callFunc f (nvStr (makeNixStringWithoutContext key)) toValue . M.fromList . zip (map fst pairs) $ values filter_ @@ -745,7 +746,7 @@ baseNameOf :: MonadNix e t f m => NValue t f m -> m (NValue t f m) baseNameOf x = do ns <- coerceToString callFunc DontCopyToStore CoerceStringy x pure $ nvStr - (principledModifyNixContents (Text.pack . takeFileName . Text.unpack) ns) + (modifyNixContents (Text.pack . takeFileName . Text.unpack) ns) bitAnd :: forall e t f m @@ -783,7 +784,7 @@ builtinsBuiltin = (throwError $ ErrorCall "HNix does not provide builtins.builti dirOf :: MonadNix e t f m => NValue t f m -> m (NValue t f m) dirOf x = demand x $ \case NVStr ns -> pure $ nvStr - (principledModifyNixContents (Text.pack . takeDirectory . Text.unpack) ns) + (modifyNixContents (Text.pack . takeDirectory . Text.unpack) ns) NVPath path -> pure $ nvPath $ takeDirectory path v -> throwError $ ErrorCall $ "dirOf: expected string or path, got " ++ show v @@ -793,7 +794,7 @@ unsafeDiscardStringContext :: MonadNix e t f m => NValue t f m -> m (NValue t f m) unsafeDiscardStringContext mnv = do ns <- fromValue mnv - toValue $ principledMakeNixStringWithoutContext $ principledStringIgnoreContext + toValue $ makeNixStringWithoutContext $ stringIgnoreContext ns seq_ @@ -866,7 +867,7 @@ instance Comonad f => Eq (WValue t f m) where WValue (NVConstant (NFloat x)) == WValue (NVConstant (NFloat y)) = x == y WValue (NVPath x ) == WValue (NVPath y ) = x == y WValue (NVStr x) == WValue (NVStr y) = - hackyStringIgnoreContext x == hackyStringIgnoreContext y + stringIgnoreContext x == stringIgnoreContext y _ == _ = False instance Comonad f => Ord (WValue t f m) where @@ -878,7 +879,7 @@ instance Comonad f => Ord (WValue t f m) where WValue (NVConstant (NFloat x)) <= WValue (NVConstant (NFloat y)) = x <= y WValue (NVPath x ) <= WValue (NVPath y ) = x <= y WValue (NVStr x) <= WValue (NVStr y) = - hackyStringIgnoreContext x <= hackyStringIgnoreContext y + stringIgnoreContext x <= stringIgnoreContext y _ <= _ = False genericClosure @@ -929,7 +930,7 @@ replaceStrings replaceStrings tfrom tto ts = fromValue (Deeper tfrom) >>= \(nsFrom :: [NixString]) -> fromValue (Deeper tto) >>= \(nsTo :: [NixString]) -> fromValue ts >>= \(ns :: NixString) -> do - let from = map principledStringIgnoreContext nsFrom + let from = map stringIgnoreContext nsFrom when (length nsFrom /= length nsTo) $ throwError $ ErrorCall @@ -942,14 +943,14 @@ replaceStrings tfrom tto ts = fromValue (Deeper tfrom) >>= \(nsFrom :: [NixStrin let rest = Text.drop (Text.length prefix) s pure (prefix, replacement, rest) finish b = - principledMakeNixString (LazyText.toStrict $ Builder.toLazyText b) + makeNixString (LazyText.toStrict $ Builder.toLazyText b) go orig result ctx = case lookupPrefix orig of Nothing -> case Text.uncons orig of Nothing -> finish result ctx Just (h, t) -> go t (result <> Builder.singleton h) ctx Just (prefix, replacementNS, rest) -> - let replacement = principledStringIgnoreContext replacementNS - newCtx = principledGetContext replacementNS + let replacement = stringIgnoreContext replacementNS + newCtx = NixString.getContext replacementNS in case prefix of "" -> case Text.uncons rest of Nothing -> finish @@ -968,8 +969,8 @@ replaceStrings tfrom tto ts = fromValue (Deeper tfrom) >>= \(nsFrom :: [NixStrin (result <> Builder.fromText replacement) (ctx <> newCtx) toValue - $ go (principledStringIgnoreContext ns) mempty - $ principledGetContext ns + $ go (stringIgnoreContext ns) mempty + $ NixString.getContext ns removeAttrs :: forall e t f m @@ -1015,14 +1016,11 @@ toFile toFile name s = do name' <- fromStringNoContext =<< fromValue name s' <- fromValue s - -- TODO Using hacky here because we still need to turn the context into - -- runtime references of the resulting file. - -- See prim_toFile in nix/src/libexpr/primops.cc mres <- toFile_ (Text.unpack name') - (Text.unpack $ hackyStringIgnoreContext s') + (Text.unpack $ stringIgnoreContext s') let t = Text.pack $ unStorePath mres sc = StringContext t DirectPath - toValue $ principledMakeNixStringWithSingletonContext t sc + toValue $ makeNixStringWithSingletonContext t sc toPath :: MonadNix e t f m => NValue t f m -> m (NValue t f m) toPath = fromValue @Path >=> toValue @Path @@ -1030,7 +1028,7 @@ toPath = fromValue @Path >=> toValue @Path pathExists_ :: MonadNix e t f m => NValue t f m -> m (NValue t f m) pathExists_ path = demand path $ \case NVPath p -> toValue =<< pathExists p - NVStr ns -> toValue =<< pathExists (Text.unpack (hackyStringIgnoreContext ns)) + NVStr ns -> toValue =<< pathExists (Text.unpack (stringIgnoreContext ns)) v -> throwError $ ErrorCall @@ -1084,7 +1082,7 @@ isFunction func = demand func $ \case throw_ :: MonadNix e t f m => NValue t f m -> m (NValue t f m) throw_ mnv = do ns <- coerceToString callFunc CopyToStore CoerceStringy mnv - throwError . ErrorCall . Text.unpack $ principledStringIgnoreContext ns + throwError . ErrorCall . Text.unpack $ stringIgnoreContext ns import_ :: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m) @@ -1115,7 +1113,7 @@ scopedImport asetArg pathArg = fromValue @(AttrSet (NValue t f m)) asetArg >>= \ getEnv_ :: MonadNix e t f m => NValue t f m -> m (NValue t f m) getEnv_ = fromValue >=> fromStringNoContext >=> \s -> do mres <- getEnvVar (Text.unpack s) - toValue $ principledMakeNixStringWithoutContext $ maybe "" Text.pack mres + toValue $ makeNixStringWithoutContext $ maybe "" Text.pack mres sort_ :: MonadNix e t f m @@ -1156,7 +1154,7 @@ lessThan ta tb = demand ta $ \va -> demand tb $ \vb -> do (NFloat a, NFloat b) -> pure $ a < b _ -> badType (NVStr a, NVStr b) -> - pure $ principledStringIgnoreContext a < principledStringIgnoreContext b + pure $ stringIgnoreContext a < stringIgnoreContext b _ -> badType concatLists @@ -1203,7 +1201,7 @@ hashString :: forall e t f m. MonadNix e t f m => NixString -> NixString -> Prim m NixString hashString nsAlgo ns = Prim $ do algo <- fromStringNoContext nsAlgo - let f g = pure $ principledModifyNixContents g ns + let f g = pure $ modifyNixContents g ns case algo of "md5" -> f $ \s -> @@ -1227,11 +1225,11 @@ hashString nsAlgo ns = Prim $ do placeHolder :: MonadNix e t f m => NValue t f m -> m (NValue t f m) placeHolder = fromValue >=> fromStringNoContext >=> \t -> do h <- runPrim - (hashString (principledMakeNixStringWithoutContext "sha256") - (principledMakeNixStringWithoutContext ("nix-output:" <> t)) + (hashString (makeNixStringWithoutContext "sha256") + (makeNixStringWithoutContext ("nix-output:" <> t)) ) toValue - $ principledMakeNixStringWithoutContext + $ makeNixStringWithoutContext $ Text.cons '/' $ Base32.encode $ case Base16.decode (text h) of -- The result coming out of hashString is base16 encoded @@ -1243,12 +1241,12 @@ placeHolder = fromValue >=> fromStringNoContext >=> \t -> do (_, e) -> error $ "Couldn't Base16 decode the text: '" <> show (text h) <> "'.\nUndecodable remainder: '" <> show e <> "'." #endif where - text h = encodeUtf8 $ principledStringIgnoreContext h + text h = encodeUtf8 $ stringIgnoreContext h absolutePathFromValue :: MonadNix e t f m => NValue t f m -> m FilePath absolutePathFromValue = \case NVStr ns -> do - let path = Text.unpack $ hackyStringIgnoreContext ns + let path = Text.unpack $ stringIgnoreContext ns unless (isAbsolute path) $ throwError $ ErrorCall @@ -1272,7 +1270,7 @@ findFile_ findFile_ aset filePath = demand aset $ \aset' -> demand filePath $ \filePath' -> case (aset', filePath') of (NVList x, NVStr ns) -> do - mres <- findPath @t @f @m x (Text.unpack (hackyStringIgnoreContext ns)) + mres <- findPath @t @f @m x (Text.unpack (stringIgnoreContext ns)) pure $ nvPath mres (NVList _, y) -> throwError $ ErrorCall $ "expected a string, got " ++ show y @@ -1289,7 +1287,7 @@ data FileType deriving (Show, Read, Eq, Ord) instance Convertible e t f m => ToValue FileType m (NValue t f m) where - toValue = toValue . principledMakeNixStringWithoutContext . \case + toValue = toValue . makeNixStringWithoutContext . \case FileTypeRegular -> "regular" :: Text FileTypeDirectory -> "directory" FileTypeSymlink -> "symlink" @@ -1321,7 +1319,7 @@ fromJSON arg = demand arg $ fromValue >=> fromStringNoContext >=> \encoded -> jsonToNValue = \case A.Object m -> flip nvSet M.empty <$> traverse jsonToNValue m A.Array l -> nvList <$> traverse jsonToNValue (V.toList l) - A.String s -> pure $ nvStr $ hackyMakeNixStringWithoutContext s + A.String s -> pure $ nvStr $ makeNixStringWithoutContext s A.Number n -> pure $ nvConstant $ case floatingOrInteger n of Left r -> NFloat r Right i -> NInt i @@ -1335,7 +1333,7 @@ toXML_ :: MonadNix e t f m => NValue t f m -> m (NValue t f m) toXML_ v = demand v $ fmap (nvStr . toXML) . normalForm typeOf :: MonadNix e t f m => NValue t f m -> m (NValue t f m) -typeOf v = demand v $ toValue . principledMakeNixStringWithoutContext . \case +typeOf v = demand v $ toValue . makeNixStringWithoutContext . \case NVConstant a -> case a of NURI _ -> "string" NInt _ -> "int" @@ -1372,7 +1370,7 @@ trace_ trace_ msg action = do traceEffect @t @f @m . Text.unpack - . principledStringIgnoreContext + . stringIgnoreContext =<< fromValue msg pure action @@ -1393,7 +1391,7 @@ exec_ xs = do -- TODO Still need to do something with the context here -- See prim_exec in nix/src/libexpr/primops.cc -- Requires the implementation of EvalState::realiseContext - exec (map (Text.unpack . hackyStringIgnoreContext) xs) + exec (map (Text.unpack . stringIgnoreContext) xs) fetchurl :: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m) @@ -1417,7 +1415,7 @@ fetchurl v = demand v $ \case $ "builtins.fetchurl: Expected URI or string, got " ++ show v - noContextAttrs ns = case principledGetStringNoContext ns of + noContextAttrs ns = case getStringNoContext ns of Nothing -> throwError $ ErrorCall $ "builtins.fetchurl: unsupported arguments to url" Just t -> pure t @@ -1440,7 +1438,7 @@ currentSystem :: MonadNix e t f m => m (NValue t f m) currentSystem = do os <- getCurrentSystemOS arch <- getCurrentSystemArch - pure $ nvStr $ principledMakeNixStringWithoutContext (arch <> "-" <> os) + pure $ nvStr $ makeNixStringWithoutContext (arch <> "-" <> os) currentTime_ :: MonadNix e t f m => m (NValue t f m) currentTime_ = do @@ -1458,7 +1456,7 @@ getContext getContext x = demand x $ \case (NVStr ns) -> do let context = - getNixLikeContext $ toNixLikeContext $ principledGetContext ns + getNixLikeContext $ toNixLikeContext $ NixString.getContext ns valued :: M.HashMap Text (NValue t f m) <- sequenceA $ M.map toValue context pure $ nvSet valued M.empty x -> @@ -1483,7 +1481,7 @@ appendContext x y = demand x $ \x' -> demand y $ \y' -> case (x', y') of Nothing -> pure [] Just os -> demand os $ \case NVList vs -> - forM vs $ fmap principledStringIgnoreContext . fromValue + forM vs $ fmap stringIgnoreContext . fromValue x -> throwError $ ErrorCall @@ -1496,13 +1494,13 @@ appendContext x y = demand x $ \x' -> demand y $ \y' -> case (x', y') of $ "Invalid types for context value in builtins.appendContext: " ++ show x toValue - $ principledMakeNixString (principledStringIgnoreContext ns) + $ makeNixString (stringIgnoreContext ns) $ fromNixLikeContext $ NixLikeContext $ M.unionWith (<>) newContextValues $ getNixLikeContext $ toNixLikeContext - $ principledGetContext ns + $ NixString.getContext ns (x, y) -> throwError $ ErrorCall diff --git a/src/Nix/Convert.hs b/src/Nix/Convert.hs index 93192da56..ec228c783 100644 --- a/src/Nix/Convert.hs +++ b/src/Nix/Convert.hs @@ -151,7 +151,7 @@ instance ( Convertible e t f m NVStr' ns -> pure $ Just ns NVPath' p -> Just - . (\s -> principledMakeNixStringWithSingletonContext s (StringContext s DirectPath)) + . (\s -> makeNixStringWithSingletonContext s (StringContext s DirectPath)) . Text.pack . unStorePath <$> addPath p @@ -166,7 +166,7 @@ instance ( Convertible e t f m instance Convertible e t f m => FromValue ByteString m (NValue' t f m (NValue t f m)) where fromValueMay = \case - NVStr' ns -> pure $ encodeUtf8 <$> hackyGetStringNoContext ns + NVStr' ns -> pure $ encodeUtf8 <$> getStringNoContext ns _ -> pure Nothing fromValue v = fromValueMay v >>= \case Just b -> pure b @@ -181,7 +181,7 @@ instance ( Convertible e t f m => FromValue Path m (NValue' t f m (NValue t f m)) where fromValueMay = \case NVPath' p -> pure $ Just (Path p) - NVStr' ns -> pure $ Path . Text.unpack <$> hackyGetStringNoContext ns + NVStr' ns -> pure $ Path . Text.unpack <$> getStringNoContext ns NVSet' s _ -> case M.lookup "outPath" s of Nothing -> pure Nothing Just p -> fromValueMay @Path p @@ -303,7 +303,7 @@ instance Convertible e t f m instance Convertible e t f m => ToValue ByteString m (NValue' t f m (NValue t f m)) where - toValue = pure . nvStr' . hackyMakeNixStringWithoutContext . decodeUtf8 + toValue = pure . nvStr' . makeNixStringWithoutContext . decodeUtf8 instance Convertible e t f m => ToValue Path m (NValue' t f m (NValue t f m)) where @@ -317,7 +317,7 @@ instance ( Convertible e t f m ) => ToValue SourcePos m (NValue' t f m (NValue t f m)) where toValue (SourcePos f l c) = do - f' <- toValue (principledMakeNixStringWithoutContext (Text.pack f)) + f' <- toValue (makeNixStringWithoutContext (Text.pack f)) l' <- toValue (unPos l) c' <- toValue (unPos c) let pos = M.fromList [("file" :: Text, f'), ("line", l'), ("column", c')] @@ -359,7 +359,7 @@ instance Convertible e t f m else pure Nothing outputs <- do let outputs = - principledMakeNixStringWithoutContext <$> nlcvOutputs nlcv + makeNixStringWithoutContext <$> nlcvOutputs nlcv ts :: [NValue t f m] <- traverse toValue outputs case ts of [] -> pure Nothing diff --git a/src/Nix/Effects/Basic.hs b/src/Nix/Effects/Basic.hs index 44535e85b..caacd4e89 100644 --- a/src/Nix/Effects/Basic.hs +++ b/src/Nix/Effects/Basic.hs @@ -137,7 +137,7 @@ findPathBy finder ls name = do Nothing -> tryPath path Nothing Just pf -> demand pf $ fromValueMay >=> \case Just (nsPfx :: NixString) -> - let pfx = hackyStringIgnoreContext nsPfx + let pfx = stringIgnoreContext nsPfx in if not (Text.null pfx) then tryPath path (Just (Text.unpack pfx)) else tryPath path Nothing @@ -174,7 +174,7 @@ fetchTarball = flip demand $ \case where go :: Maybe (NValue t f m) -> NValue t f m -> m (NValue t f m) go msha = \case - NVStr ns -> fetch (hackyStringIgnoreContext ns) msha + NVStr ns -> fetch (stringIgnoreContext ns) msha v -> throwError $ ErrorCall @@ -197,7 +197,7 @@ fetchTarball = flip demand $ \case fetch uri Nothing = nixInstantiateExpr $ "builtins.fetchTarball \"" ++ Text.unpack uri ++ "\"" fetch url (Just t) = demand t $ fromValue >=> \nsSha -> - let sha = hackyStringIgnoreContext nsSha + let sha = stringIgnoreContext nsSha in nixInstantiateExpr $ "builtins.fetchTarball { " ++ "url = \"" diff --git a/src/Nix/Effects/Derivation.hs b/src/Nix/Effects/Derivation.hs index 51a0f3b16..804c5be1c 100644 --- a/src/Nix/Effects/Derivation.hs +++ b/src/Nix/Effects/Derivation.hs @@ -260,8 +260,8 @@ defaultDerivationStrict = fromValue @(AttrSet (NValue t f m)) >=> \s -> do drvHash <- Store.encodeInBase Store.Base16 <$> hashDerivationModulo drv' modify (\(a, b) -> (a, MS.insert drvPath drvHash b)) - let outputsWithContext = Map.mapWithKey (\out path -> principledMakeNixStringWithSingletonContext path (StringContext drvPath (DerivationOutput out))) (outputs drv') - drvPathWithContext = principledMakeNixStringWithSingletonContext drvPath (StringContext drvPath AllOutputs) + let outputsWithContext = Map.mapWithKey (\out path -> makeNixStringWithSingletonContext path (StringContext drvPath (DerivationOutput out))) (outputs drv') + drvPathWithContext = makeNixStringWithSingletonContext drvPath (StringContext drvPath AllOutputs) attrSet = M.map nvStr $ M.fromList $ ("drvPath", drvPathWithContext): Map.toList outputsWithContext -- TODO: Add location information for all the entries. -- here --v @@ -373,7 +373,7 @@ buildDerivationWithContext drvAttrs = do return name extractNoCtx :: MonadNix e t f m => NixString -> WithStringContextT m Text - extractNoCtx ns = case principledGetStringNoContext ns of + extractNoCtx ns = case getStringNoContext ns of Nothing -> lift $ throwError $ ErrorCall $ "The string " ++ show ns ++ " is not allowed to have a context." Just v -> return v diff --git a/src/Nix/Eval.hs b/src/Nix/Eval.hs index 684ea1aec..b691d26c8 100644 --- a/src/Nix/Eval.hs +++ b/src/Nix/Eval.hs @@ -355,7 +355,7 @@ evalSetterKeyName = \case StaticKey k -> pure (Just k) DynamicKey k -> runAntiquoted "\n" assembleString (>>= fromValueMay) k <&> \case - Just ns -> Just (hackyStringIgnoreContext ns) + Just ns -> Just (stringIgnoreContext ns) _ -> Nothing assembleString @@ -367,10 +367,10 @@ assembleString = \case Indented _ parts -> fromParts parts DoubleQuoted parts -> fromParts parts where - fromParts = fmap (fmap principledStringMConcat . sequence) . traverse go + fromParts = fmap (fmap mconcat . sequence) . traverse go go = runAntiquoted "\n" - (pure . Just . principledMakeNixStringWithoutContext) + (pure . Just . makeNixStringWithoutContext) (>>= fromValueMay) buildArgument diff --git a/src/Nix/Exec.hs b/src/Nix/Exec.hs index da3ab298f..c5bf60b74 100644 --- a/src/Nix/Exec.hs +++ b/src/Nix/Exec.hs @@ -210,7 +210,7 @@ instance MonadNix e t f m => MonadEval (NValue t f m) m where pure $ nvStrP (Provenance scope - (NStr_ span (DoubleQuoted [Plain (hackyStringIgnoreContext ns)])) + (NStr_ span (DoubleQuoted [Plain (stringIgnoreContext ns)])) ) ns Nothing -> nverr $ ErrorCall "Failed to assemble string" @@ -400,11 +400,11 @@ execBinaryOpForced scope span op lval rval = case op of NPlus -> case (lval, rval) of (NVConstant _, NVConstant _) -> numBinOp (+) - (NVStr ls, NVStr rs) -> pure $ nvStrP prov (ls `principledStringMappend` rs) + (NVStr ls, NVStr rs) -> pure $ nvStrP prov (ls `mappend` rs) (NVStr ls, rs@NVPath{}) -> - (\rs2 -> nvStrP prov (ls `principledStringMappend` rs2)) + (\rs2 -> nvStrP prov (ls `mappend` rs2)) <$> coerceToString callFunc CopyToStore CoerceStringy rs - (NVPath ls, NVStr rs) -> case principledGetStringNoContext rs of + (NVPath ls, NVStr rs) -> case getStringNoContext rs of Just rs2 -> nvPathP prov <$> makeAbsolutePath @t @f (ls `mappend` Text.unpack rs2) Nothing -> throwError $ ErrorCall $ -- data/nix/src/libexpr/eval.cc:1412 @@ -412,10 +412,10 @@ execBinaryOpForced scope span op lval rval = case op of (NVPath ls, NVPath rs) -> nvPathP prov <$> makeAbsolutePath @t @f (ls ++ rs) (ls@NVSet{}, NVStr rs) -> - (\ls2 -> nvStrP prov (ls2 `principledStringMappend` rs)) + (\ls2 -> nvStrP prov (ls2 `mappend` rs)) <$> coerceToString callFunc DontCopyToStore CoerceStringy ls (NVStr ls, rs@NVSet{}) -> - (\rs2 -> nvStrP prov (ls `principledStringMappend` rs2)) + (\rs2 -> nvStrP prov (ls `mappend` rs2)) <$> coerceToString callFunc DontCopyToStore CoerceStringy rs _ -> unsupportedTypes @@ -473,7 +473,7 @@ execBinaryOpForced scope span op lval rval = case op of -- This function is here, rather than in 'Nix.String', because of the need to -- use 'throwError'. fromStringNoContext :: Framed e m => NixString -> m Text -fromStringNoContext ns = case principledGetStringNoContext ns of +fromStringNoContext ns = case getStringNoContext ns of Just str -> pure str Nothing -> throwError $ ErrorCall $ "expected string with no context, but got " ++ show ns diff --git a/src/Nix/Normal.hs b/src/Nix/Normal.hs index 24658d0ba..b09709449 100644 --- a/src/Nix/Normal.hs +++ b/src/Nix/Normal.hs @@ -124,7 +124,7 @@ removeEffects = (fmap Free . sequenceNValue' id) opaque :: Applicative f => NValue t f m -opaque = nvStr $ principledMakeNixStringWithoutContext "" +opaque = nvStr $ makeNixStringWithoutContext "" dethunk :: (MonadThunk t m (NValue t f m), MonadDataContext f m) diff --git a/src/Nix/Pretty.hs b/src/Nix/Pretty.hs index 51149cabe..df3aa3ac6 100644 --- a/src/Nix/Pretty.hs +++ b/src/Nix/Pretty.hs @@ -330,7 +330,7 @@ valueToExpr = iterNValue (\_ _ -> thk) phi phi (NVBuiltin' name _) = Fix . NSym . pack $ "builtins." ++ name phi _ = error "Pattern synonyms foil completeness check" - mkStr ns = Fix $ NStr $ DoubleQuoted [Plain (hackyStringIgnoreContext ns)] + mkStr ns = Fix $ NStr $ DoubleQuoted [Plain (stringIgnoreContext ns)] prettyNValue :: forall t f m ann . MonadDataContext f m => NValue t f m -> Doc ann @@ -390,7 +390,7 @@ printNix = iterNValue (\_ _ -> thk) phi phi :: NValue' t f m String -> String phi (NVConstant' a ) = unpack $ atomText a - phi (NVStr' ns) = show $ hackyStringIgnoreContext ns + phi (NVStr' ns) = show $ stringIgnoreContext ns phi (NVList' l ) = "[ " ++ unwords l ++ " ]" phi (NVSet' s _) = "{ " diff --git a/src/Nix/String.hs b/src/Nix/String.hs index b9b9ab7cf..cd0008876 100644 --- a/src/Nix/String.hs +++ b/src/Nix/String.hs @@ -1,12 +1,10 @@ {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE OverloadedStrings #-} -{-# OPTIONS_GHC -Wno-unused-top-binds #-} + module Nix.String ( NixString - , principledGetContext - , principledMakeNixString - , principledMempty + , getContext + , makeNixString , StringContext(..) , ContextFlavor(..) , NixLikeContext(..) @@ -14,18 +12,12 @@ module Nix.String , toNixLikeContext , fromNixLikeContext , stringHasContext - , principledIntercalateNixString - , hackyGetStringNoContext - , principledGetStringNoContext - , principledStringIgnoreContext - , hackyStringIgnoreContext - , hackyMakeNixStringWithoutContext - , principledMakeNixStringWithoutContext - , principledMakeNixStringWithSingletonContext - , principledModifyNixContents - , principledStringMappend - , principledStringMempty - , principledStringMConcat + , intercalateNixString + , getStringNoContext + , stringIgnoreContext + , makeNixStringWithoutContext + , makeNixStringWithSingletonContext + , modifyNixContents , WithStringContext , WithStringContextT(..) , extractNixString @@ -47,16 +39,10 @@ import Data.Text ( Text ) import qualified Data.Text as Text import GHC.Generics --- {-# WARNING hackyGetStringNoContext, hackyStringIgnoreContext, hackyMakeNixStringWithoutContext "This NixString function needs to be replaced" #-} --- | A 'ContextFlavor' describes the sum of possible derivations for string contexts -data ContextFlavor = - DirectPath - | AllOutputs - | DerivationOutput !Text - deriving (Show, Eq, Ord, Generic) +-- * Types -instance Hashable ContextFlavor +-- ** Context -- | A 'StringContext' ... data StringContext = @@ -66,12 +52,14 @@ data StringContext = instance Hashable StringContext -data NixString = NixString - { nsContents :: !Text - , nsContext :: !(S.HashSet StringContext) - } deriving (Eq, Ord, Show, Generic) +-- | A 'ContextFlavor' describes the sum of possible derivations for string contexts +data ContextFlavor = + DirectPath + | AllOutputs + | DerivationOutput !Text + deriving (Show, Eq, Ord, Generic) -instance Hashable NixString +instance Hashable ContextFlavor newtype NixLikeContext = NixLikeContext { getNixLikeContext :: M.HashMap Text NixLikeContextValue @@ -93,131 +81,104 @@ instance Semigroup NixLikeContextValue where instance Monoid NixLikeContextValue where mempty = NixLikeContextValue False False [] -toStringContexts :: (Text, NixLikeContextValue) -> [StringContext] -toStringContexts (path, nlcv) = case nlcv of - NixLikeContextValue True _ _ -> StringContext path DirectPath - : toStringContexts (path, nlcv { nlcvPath = False }) - NixLikeContextValue _ True _ -> StringContext path AllOutputs - : toStringContexts (path, nlcv { nlcvAllOutputs = False }) - NixLikeContextValue _ _ ls | not (null ls) -> - map (StringContext path . DerivationOutput) ls - _ -> [] -toNixLikeContextValue :: StringContext -> (Text, NixLikeContextValue) -toNixLikeContextValue sc = (,) (scPath sc) $ case scFlavor sc of - DirectPath -> NixLikeContextValue True False [] - AllOutputs -> NixLikeContextValue False True [] - DerivationOutput t -> NixLikeContextValue False False [t] +-- ** StringContext accumulator -toNixLikeContext :: S.HashSet StringContext -> NixLikeContext -toNixLikeContext stringContext = NixLikeContext - $ S.foldr go mempty stringContext - where - go sc hm = - let (t, nlcv) = toNixLikeContextValue sc in M.insertWith (<>) t nlcv hm +-- | A monad for accumulating string context while producing a result string. +newtype WithStringContextT m a = WithStringContextT (WriterT (S.HashSet StringContext) m a) + deriving (Functor, Applicative, Monad, MonadTrans, MonadWriter (S.HashSet StringContext)) -fromNixLikeContext :: NixLikeContext -> S.HashSet StringContext -fromNixLikeContext = - S.fromList . join . map toStringContexts . M.toList . getNixLikeContext +type WithStringContext = WithStringContextT Identity -principledGetContext :: NixString -> S.HashSet StringContext -principledGetContext = nsContext --- | Combine two NixStrings using mappend -principledMempty :: NixString -principledMempty = NixString "" mempty +-- ** NixString --- | Combine two NixStrings using mappend -principledStringMappend :: NixString -> NixString -> NixString -principledStringMappend (NixString s1 t1) (NixString s2 t2) = - NixString (s1 <> s2) (t1 <> t2) +data NixString = NixString + { nsContents :: !Text + , nsContext :: !(S.HashSet StringContext) + } deriving (Eq, Ord, Show, Generic) --- 2021-01-02: NOTE: This function is ERRADICATED from the source code. --- ERRADICATE it from the API. --- | Combine two NixStrings using mappend -hackyStringMappend :: NixString -> NixString -> NixString -hackyStringMappend (NixString s1 t1) (NixString s2 t2) = - NixString (s1 <> s2) (t1 <> t2) +instance Semigroup NixString where + NixString s1 t1 <> NixString s2 t2 = NixString (s1 <> s2) (t1 <> t2) --- | Combine NixStrings with a separator -principledIntercalateNixString :: NixString -> [NixString] -> NixString -principledIntercalateNixString _ [] = principledMempty -principledIntercalateNixString _ [ns] = ns -principledIntercalateNixString sep nss = NixString contents ctx - where - contents = Text.intercalate (nsContents sep) (map nsContents nss) - ctx = S.unions (nsContext sep : map nsContext nss) +instance Monoid NixString where + mempty = NixString mempty mempty --- 2021-01-02: NOTE: This function is ERRADICATED from the source code. --- ERRADICATE it from the API. --- | Combine NixStrings using mconcat -hackyStringMConcat :: [NixString] -> NixString -hackyStringMConcat = foldr principledStringMappend (NixString mempty mempty) +instance Hashable NixString --- | Empty string with empty context. -principledStringMempty :: NixString -principledStringMempty = NixString mempty mempty --- | Combine NixStrings using mconcat -principledStringMConcat :: [NixString] -> NixString -principledStringMConcat = - foldr principledStringMappend (NixString mempty mempty) +-- * Functions ---instance Semigroup NixString where - --NixString s1 t1 <> NixString s2 t2 = NixString (s1 <> s2) (t1 <> t2) +-- ** Makers ---instance Monoid NixString where --- mempty = NixString mempty mempty --- mappend = (<>) +-- | Constructs NixString without a context +makeNixStringWithoutContext :: Text -> NixString +makeNixStringWithoutContext = flip NixString mempty --- | Extract the string contents from a NixString that has no context -hackyGetStringNoContext :: NixString -> Maybe Text -hackyGetStringNoContext (NixString s c) | null c = Just s - | otherwise = Nothing +-- | Create NixString using a singleton context +makeNixStringWithSingletonContext + :: Text -> StringContext -> NixString +makeNixStringWithSingletonContext s c = NixString s (S.singleton c) --- | Extract the string contents from a NixString that has no context -principledGetStringNoContext :: NixString -> Maybe Text -principledGetStringNoContext (NixString s c) | null c = Just s - | otherwise = Nothing +-- | Create NixString from a Text and context +makeNixString :: Text -> S.HashSet StringContext -> NixString +makeNixString = NixString --- | Extract the string contents from a NixString even if the NixString has an associated context -principledStringIgnoreContext :: NixString -> Text -principledStringIgnoreContext (NixString s _) = s --- | Extract the string contents from a NixString even if the NixString has an associated context -hackyStringIgnoreContext :: NixString -> Text -hackyStringIgnoreContext (NixString s _) = s +-- ** Checkers -- | Returns True if the NixString has an associated context stringHasContext :: NixString -> Bool stringHasContext (NixString _ c) = not (null c) --- | Constructs a NixString without a context -hackyMakeNixStringWithoutContext :: Text -> NixString -hackyMakeNixStringWithoutContext = flip NixString mempty --- | Constructs a NixString without a context -principledMakeNixStringWithoutContext :: Text -> NixString -principledMakeNixStringWithoutContext = flip NixString mempty +-- ** Getters --- | Modify the string part of the NixString, leaving the context unchanged -principledModifyNixContents :: (Text -> Text) -> NixString -> NixString -principledModifyNixContents f (NixString s c) = NixString (f s) c +getContext :: NixString -> S.HashSet StringContext +getContext = nsContext --- | Create a NixString using a singleton context -principledMakeNixStringWithSingletonContext - :: Text -> StringContext -> NixString -principledMakeNixStringWithSingletonContext s c = NixString s (S.singleton c) +fromNixLikeContext :: NixLikeContext -> S.HashSet StringContext +fromNixLikeContext = + S.fromList . join . map toStringContexts . M.toList . getNixLikeContext --- | Create a NixString from a Text and context -principledMakeNixString :: Text -> S.HashSet StringContext -> NixString -principledMakeNixString = NixString +-- | Extract the string contents from a NixString that has no context +getStringNoContext :: NixString -> Maybe Text +getStringNoContext (NixString s c) | null c = Just s + | otherwise = Nothing --- | A monad for accumulating string context while producing a result string. -newtype WithStringContextT m a = WithStringContextT (WriterT (S.HashSet StringContext) m a) - deriving (Functor, Applicative, Monad, MonadTrans, MonadWriter (S.HashSet StringContext)) +-- | Extract the string contents from a NixString even if the NixString has an associated context +stringIgnoreContext :: NixString -> Text +stringIgnoreContext (NixString s _) = s -type WithStringContext = WithStringContextT Identity +-- | Get the contents of a 'NixString' and write its context into the resulting set. +extractNixString :: Monad m => NixString -> WithStringContextT m Text +extractNixString (NixString s c) = WithStringContextT $ tell c >> pure s + + +-- ** Setters + +toStringContexts :: (Text, NixLikeContextValue) -> [StringContext] +toStringContexts (path, nlcv) = case nlcv of + NixLikeContextValue True _ _ -> StringContext path DirectPath + : toStringContexts (path, nlcv { nlcvPath = False }) + NixLikeContextValue _ True _ -> StringContext path AllOutputs + : toStringContexts (path, nlcv { nlcvAllOutputs = False }) + NixLikeContextValue _ _ ls | not (null ls) -> + map (StringContext path . DerivationOutput) ls + _ -> [] + +toNixLikeContextValue :: StringContext -> (Text, NixLikeContextValue) +toNixLikeContextValue sc = (,) (scPath sc) $ case scFlavor sc of + DirectPath -> NixLikeContextValue True False [] + AllOutputs -> NixLikeContextValue False True [] + DerivationOutput t -> NixLikeContextValue False False [t] + +toNixLikeContext :: S.HashSet StringContext -> NixLikeContext +toNixLikeContext stringContext = NixLikeContext + $ S.foldr go mempty stringContext + where + go sc hm = + let (t, nlcv) = toNixLikeContextValue sc in M.insertWith (<>) t nlcv hm -- | Add 'StringContext's into the resulting set. addStringContext @@ -228,25 +189,38 @@ addStringContext = WithStringContextT . tell addSingletonStringContext :: Monad m => StringContext -> WithStringContextT m () addSingletonStringContext = WithStringContextT . tell . S.singleton --- | Get the contents of a 'NixString' and write its context into the resulting set. -extractNixString :: Monad m => NixString -> WithStringContextT m Text -extractNixString (NixString s c) = WithStringContextT $ tell c >> pure s - -- | Run an action producing a string with a context and put those into a 'NixString'. runWithStringContextT :: Monad m => WithStringContextT m Text -> m NixString runWithStringContextT (WithStringContextT m) = uncurry NixString <$> runWriterT m +-- | Run an action producing a string with a context and put those into a 'NixString'. +runWithStringContext :: WithStringContextT Identity Text -> NixString +runWithStringContext = runIdentity . runWithStringContextT + + +-- ** Modifiers + +-- | Modify the string part of the NixString, leaving the context unchanged +modifyNixContents :: (Text -> Text) -> NixString -> NixString +modifyNixContents f (NixString s c) = NixString (f s) c + -- | Run an action that manipulates nix strings, and collect the contexts encountered. -- Warning: this may be unsafe, depending on how you handle the resulting context list. runWithStringContextT' :: Monad m => WithStringContextT m a -> m (a, S.HashSet StringContext) runWithStringContextT' (WithStringContextT m) = runWriterT m --- | Run an action producing a string with a context and put those into a 'NixString'. -runWithStringContext :: WithStringContextT Identity Text -> NixString -runWithStringContext = runIdentity . runWithStringContextT - -- | Run an action that manipulates nix strings, and collect the contexts encountered. -- Warning: this may be unsafe, depending on how you handle the resulting context list. runWithStringContext' :: WithStringContextT Identity a -> (a, S.HashSet StringContext) runWithStringContext' = runIdentity . runWithStringContextT' + +-- | Combine NixStrings with a separator +intercalateNixString :: NixString -> [NixString] -> NixString +intercalateNixString _ [] = mempty +intercalateNixString _ [ns] = ns +intercalateNixString sep nss = NixString contents ctx + where + contents = Text.intercalate (nsContents sep) (map nsContents nss) + ctx = S.unions (nsContext sep : map nsContext nss) + diff --git a/src/Nix/String/Coerce.hs b/src/Nix/String/Coerce.hs index c110281de..641888d01 100644 --- a/src/Nix/String/Coerce.hs +++ b/src/Nix/String/Coerce.hs @@ -57,18 +57,18 @@ coerceToString call ctsm clevel = go | -- TODO Return a singleton for "" and "1" b && clevel == CoerceAny -> pure - $ principledMakeNixStringWithoutContext "1" - | clevel == CoerceAny -> pure $ principledMakeNixStringWithoutContext "" + $ makeNixStringWithoutContext "1" + | clevel == CoerceAny -> pure $ makeNixStringWithoutContext "" NVConstant (NInt n) | clevel == CoerceAny -> - pure $ principledMakeNixStringWithoutContext $ Text.pack $ show n + pure $ makeNixStringWithoutContext $ Text.pack $ show n NVConstant (NFloat n) | clevel == CoerceAny -> - pure $ principledMakeNixStringWithoutContext $ Text.pack $ show n + pure $ makeNixStringWithoutContext $ Text.pack $ show n NVConstant NNull | clevel == CoerceAny -> - pure $ principledMakeNixStringWithoutContext "" + pure $ makeNixStringWithoutContext "" NVStr ns -> pure ns NVPath p | ctsm == CopyToStore -> storePathToNixString <$> addPath p - | otherwise -> pure $ principledMakeNixStringWithoutContext $ Text.pack p + | otherwise -> pure $ makeNixStringWithoutContext $ Text.pack p NVList l | clevel == CoerceAny -> nixStringUnwords <$> traverse (`demand` go) l @@ -80,9 +80,9 @@ coerceToString call ctsm clevel = go v -> throwError $ ErrorCall $ "Expected a string, but saw: " ++ show v nixStringUnwords = - principledIntercalateNixString (principledMakeNixStringWithoutContext " ") + intercalateNixString (makeNixStringWithoutContext " ") storePathToNixString :: StorePath -> NixString - storePathToNixString sp = principledMakeNixStringWithSingletonContext + storePathToNixString sp = makeNixStringWithSingletonContext t (StringContext t DirectPath) where t = Text.pack $ unStorePath sp diff --git a/src/Nix/Value.hs b/src/Nix/Value.hs index 895767752..3c9979eb0 100644 --- a/src/Nix/Value.hs +++ b/src/Nix/Value.hs @@ -85,7 +85,7 @@ instance Foldable (NValueF p m) where instance Show r => Show (NValueF p m r) where showsPrec = flip go where go (NVConstantF atom ) = showsCon1 "NVConstant" atom - go (NVStrF ns ) = showsCon1 "NVStr" (hackyStringIgnoreContext ns) + go (NVStrF ns ) = showsCon1 "NVStr" (stringIgnoreContext ns) go (NVListF lst ) = showsCon1 "NVList" lst go (NVSetF attrs _) = showsCon1 "NVSet" attrs go (NVClosureF p _) = showsCon1 "NVClosure" p @@ -176,7 +176,7 @@ instance Comonad f => Show1 (NValue' t f m) where liftShowsPrec sp sl p = \case NVConstant' atom -> showsUnaryWith showsPrec "NVConstantF" p atom NVStr' ns -> - showsUnaryWith showsPrec "NVStrF" p (hackyStringIgnoreContext ns) + showsUnaryWith showsPrec "NVStrF" p (stringIgnoreContext ns) NVList' lst -> showsUnaryWith (liftShowsPrec sp sl) "NVListF" p lst NVSet' attrs _ -> showsUnaryWith (liftShowsPrec sp sl) "NVSetF" p attrs NVPath' path -> showsUnaryWith showsPrec "NVPathF" p path diff --git a/src/Nix/Value/Equal.hs b/src/Nix/Value/Equal.hs index ccdcd02be..1a8c16c4c 100644 --- a/src/Nix/Value/Equal.hs +++ b/src/Nix/Value/Equal.hs @@ -86,7 +86,7 @@ isDerivationM f m = case M.lookup "type" m of case mres of -- We should probably really make sure the context is empty here -- but the C++ implementation ignores it. - Just s -> pure $ principledStringIgnoreContext s == "derivation" + Just s -> pure $ stringIgnoreContext s == "derivation" Nothing -> pure False isDerivation :: Monad m => (t -> Maybe NixString) -> AttrSet t -> Bool @@ -104,7 +104,7 @@ valueFEqM attrsEq eq = curry $ \case (NVConstantF (NInt x), NVConstantF (NFloat y)) -> pure $ fromInteger x == y (NVConstantF lc , NVConstantF rc ) -> pure $ lc == rc (NVStrF ls, NVStrF rs) -> - pure $ principledStringIgnoreContext ls == principledStringIgnoreContext rs + pure $ stringIgnoreContext ls == stringIgnoreContext rs (NVListF ls , NVListF rs ) -> alignEqM eq ls rs (NVSetF lm _, NVSetF rm _) -> attrsEq lm rm (NVPathF lp , NVPathF rp ) -> pure $ lp == rp diff --git a/tests/Main.hs b/tests/Main.hs index 285db09eb..b0fcb75cd 100644 --- a/tests/Main.hs +++ b/tests/Main.hs @@ -59,7 +59,7 @@ ensureNixpkgsCanParse = time <- getCurrentTime runWithBasicEffectsIO (defaultOptions time) $ Nix.nixEvalExprLoc Nothing expr - let dir = hackyStringIgnoreContext ns + let dir = stringIgnoreContext ns exists <- fileExist (unpack dir) unless exists $ errorWithoutStackTrace $ diff --git a/tests/NixLanguageTests.hs b/tests/NixLanguageTests.hs index d7eb83bc5..d403b27ba 100644 --- a/tests/NixLanguageTests.hs +++ b/tests/NixLanguageTests.hs @@ -133,7 +133,7 @@ assertLangOk opts file = do assertLangOkXml :: Options -> FilePath -> Assertion assertLangOkXml opts file = do - actual <- principledStringIgnoreContext . toXML <$> hnixEvalFile + actual <- stringIgnoreContext . toXML <$> hnixEvalFile opts (file ++ ".nix") expected <- Text.readFile $ file ++ ".exp.xml"