Skip to content

Commit 67fe11c

Browse files
committed
(hacky->principled)StringIgnoreContext
1 parent 3ba7e80 commit 67fe11c

File tree

8 files changed

+22
-22
lines changed

8 files changed

+22
-22
lines changed

src/Nix/Builtins.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -392,7 +392,7 @@ unsafeGetAttrPos
392392
-> m (NValue t f m)
393393
unsafeGetAttrPos x y = demand x $ \x' -> demand y $ \y' -> case (x', y') of
394394
(NVStr ns, NVSet _ apos) ->
395-
case M.lookup (hackyStringIgnoreContext ns) apos of
395+
case M.lookup (principledStringIgnoreContext ns) apos of
396396
Nothing -> pure $ nvConstant NNull
397397
Just delta -> toValue delta
398398
(x, y) ->
@@ -866,7 +866,7 @@ instance Comonad f => Eq (WValue t f m) where
866866
WValue (NVConstant (NFloat x)) == WValue (NVConstant (NFloat y)) = x == y
867867
WValue (NVPath x ) == WValue (NVPath y ) = x == y
868868
WValue (NVStr x) == WValue (NVStr y) =
869-
hackyStringIgnoreContext x == hackyStringIgnoreContext y
869+
principledStringIgnoreContext x == principledStringIgnoreContext y
870870
_ == _ = False
871871

872872
instance Comonad f => Ord (WValue t f m) where
@@ -878,7 +878,7 @@ instance Comonad f => Ord (WValue t f m) where
878878
WValue (NVConstant (NFloat x)) <= WValue (NVConstant (NFloat y)) = x <= y
879879
WValue (NVPath x ) <= WValue (NVPath y ) = x <= y
880880
WValue (NVStr x) <= WValue (NVStr y) =
881-
hackyStringIgnoreContext x <= hackyStringIgnoreContext y
881+
principledStringIgnoreContext x <= principledStringIgnoreContext y
882882
_ <= _ = False
883883

884884
genericClosure
@@ -1019,7 +1019,7 @@ toFile name s = do
10191019
-- runtime references of the resulting file.
10201020
-- See prim_toFile in nix/src/libexpr/primops.cc
10211021
mres <- toFile_ (Text.unpack name')
1022-
(Text.unpack $ hackyStringIgnoreContext s')
1022+
(Text.unpack $ principledStringIgnoreContext s')
10231023
let t = Text.pack $ unStorePath mres
10241024
sc = StringContext t DirectPath
10251025
toValue $ principledMakeNixStringWithSingletonContext t sc
@@ -1030,7 +1030,7 @@ toPath = fromValue @Path >=> toValue @Path
10301030
pathExists_ :: MonadNix e t f m => NValue t f m -> m (NValue t f m)
10311031
pathExists_ path = demand path $ \case
10321032
NVPath p -> toValue =<< pathExists p
1033-
NVStr ns -> toValue =<< pathExists (Text.unpack (hackyStringIgnoreContext ns))
1033+
NVStr ns -> toValue =<< pathExists (Text.unpack (principledStringIgnoreContext ns))
10341034
v ->
10351035
throwError
10361036
$ ErrorCall
@@ -1248,7 +1248,7 @@ placeHolder = fromValue >=> fromStringNoContext >=> \t -> do
12481248
absolutePathFromValue :: MonadNix e t f m => NValue t f m -> m FilePath
12491249
absolutePathFromValue = \case
12501250
NVStr ns -> do
1251-
let path = Text.unpack $ hackyStringIgnoreContext ns
1251+
let path = Text.unpack $ principledStringIgnoreContext ns
12521252
unless (isAbsolute path)
12531253
$ throwError
12541254
$ ErrorCall
@@ -1272,7 +1272,7 @@ findFile_
12721272
findFile_ aset filePath = demand aset $ \aset' -> demand filePath $ \filePath' ->
12731273
case (aset', filePath') of
12741274
(NVList x, NVStr ns) -> do
1275-
mres <- findPath @t @f @m x (Text.unpack (hackyStringIgnoreContext ns))
1275+
mres <- findPath @t @f @m x (Text.unpack (principledStringIgnoreContext ns))
12761276
pure $ nvPath mres
12771277
(NVList _, y) ->
12781278
throwError $ ErrorCall $ "expected a string, got " ++ show y
@@ -1393,7 +1393,7 @@ exec_ xs = do
13931393
-- TODO Still need to do something with the context here
13941394
-- See prim_exec in nix/src/libexpr/primops.cc
13951395
-- Requires the implementation of EvalState::realiseContext
1396-
exec (map (Text.unpack . hackyStringIgnoreContext) xs)
1396+
exec (map (Text.unpack . principledStringIgnoreContext) xs)
13971397

13981398
fetchurl
13991399
:: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m)

src/Nix/Effects/Basic.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -137,7 +137,7 @@ findPathBy finder ls name = do
137137
Nothing -> tryPath path Nothing
138138
Just pf -> demand pf $ fromValueMay >=> \case
139139
Just (nsPfx :: NixString) ->
140-
let pfx = hackyStringIgnoreContext nsPfx
140+
let pfx = principledStringIgnoreContext nsPfx
141141
in if not (Text.null pfx)
142142
then tryPath path (Just (Text.unpack pfx))
143143
else tryPath path Nothing
@@ -174,7 +174,7 @@ fetchTarball = flip demand $ \case
174174
where
175175
go :: Maybe (NValue t f m) -> NValue t f m -> m (NValue t f m)
176176
go msha = \case
177-
NVStr ns -> fetch (hackyStringIgnoreContext ns) msha
177+
NVStr ns -> fetch (principledStringIgnoreContext ns) msha
178178
v ->
179179
throwError
180180
$ ErrorCall
@@ -197,7 +197,7 @@ fetchTarball = flip demand $ \case
197197
fetch uri Nothing =
198198
nixInstantiateExpr $ "builtins.fetchTarball \"" ++ Text.unpack uri ++ "\""
199199
fetch url (Just t) = demand t $ fromValue >=> \nsSha ->
200-
let sha = hackyStringIgnoreContext nsSha
200+
let sha = principledStringIgnoreContext nsSha
201201
in nixInstantiateExpr
202202
$ "builtins.fetchTarball { "
203203
++ "url = \""

src/Nix/Eval.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -355,7 +355,7 @@ evalSetterKeyName = \case
355355
StaticKey k -> pure (Just k)
356356
DynamicKey k ->
357357
runAntiquoted "\n" assembleString (>>= fromValueMay) k <&> \case
358-
Just ns -> Just (hackyStringIgnoreContext ns)
358+
Just ns -> Just (principledStringIgnoreContext ns)
359359
_ -> Nothing
360360

361361
assembleString

src/Nix/Exec.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -210,7 +210,7 @@ instance MonadNix e t f m => MonadEval (NValue t f m) m where
210210
pure $ nvStrP
211211
(Provenance
212212
scope
213-
(NStr_ span (DoubleQuoted [Plain (hackyStringIgnoreContext ns)]))
213+
(NStr_ span (DoubleQuoted [Plain (principledStringIgnoreContext ns)]))
214214
)
215215
ns
216216
Nothing -> nverr $ ErrorCall "Failed to assemble string"

src/Nix/Pretty.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -330,7 +330,7 @@ valueToExpr = iterNValue (\_ _ -> thk) phi
330330
phi (NVBuiltin' name _) = Fix . NSym . pack $ "builtins." ++ name
331331
phi _ = error "Pattern synonyms foil completeness check"
332332

333-
mkStr ns = Fix $ NStr $ DoubleQuoted [Plain (hackyStringIgnoreContext ns)]
333+
mkStr ns = Fix $ NStr $ DoubleQuoted [Plain (principledStringIgnoreContext ns)]
334334

335335
prettyNValue
336336
:: forall t f m ann . MonadDataContext f m => NValue t f m -> Doc ann
@@ -390,7 +390,7 @@ printNix = iterNValue (\_ _ -> thk) phi
390390

391391
phi :: NValue' t f m String -> String
392392
phi (NVConstant' a ) = unpack $ atomText a
393-
phi (NVStr' ns) = show $ hackyStringIgnoreContext ns
393+
phi (NVStr' ns) = show $ principledStringIgnoreContext ns
394394
phi (NVList' l ) = "[ " ++ unwords l ++ " ]"
395395
phi (NVSet' s _) =
396396
"{ "

src/Nix/String.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -169,10 +169,6 @@ principledGetStringNoContext (NixString s c) | null c = Just s
169169
principledStringIgnoreContext :: NixString -> Text
170170
principledStringIgnoreContext (NixString s _) = s
171171

172-
-- | Extract the string contents from a NixString even if the NixString has an associated context
173-
hackyStringIgnoreContext :: NixString -> Text
174-
hackyStringIgnoreContext (NixString s _) = s
175-
176172
-- | Returns True if the NixString has an associated context
177173
stringHasContext :: NixString -> Bool
178174
stringHasContext (NixString _ c) = not (null c)
@@ -252,3 +248,7 @@ hackyStringMConcat = foldr principledStringMappend (NixString mempty mempty)
252248
hackyMakeNixStringWithoutContext :: Text -> NixString
253249
hackyMakeNixStringWithoutContext = principledMakeNixStringWithoutContext
254250

251+
-- | Extract the string contents from a NixString even if the NixString has an associated context
252+
hackyStringIgnoreContext :: NixString -> Text
253+
hackyStringIgnoreContext = principledStringIgnoreContext
254+

src/Nix/Value.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,7 @@ instance Foldable (NValueF p m) where
8585
instance Show r => Show (NValueF p m r) where
8686
showsPrec = flip go where
8787
go (NVConstantF atom ) = showsCon1 "NVConstant" atom
88-
go (NVStrF ns ) = showsCon1 "NVStr" (hackyStringIgnoreContext ns)
88+
go (NVStrF ns ) = showsCon1 "NVStr" (principledStringIgnoreContext ns)
8989
go (NVListF lst ) = showsCon1 "NVList" lst
9090
go (NVSetF attrs _) = showsCon1 "NVSet" attrs
9191
go (NVClosureF p _) = showsCon1 "NVClosure" p
@@ -176,7 +176,7 @@ instance Comonad f => Show1 (NValue' t f m) where
176176
liftShowsPrec sp sl p = \case
177177
NVConstant' atom -> showsUnaryWith showsPrec "NVConstantF" p atom
178178
NVStr' ns ->
179-
showsUnaryWith showsPrec "NVStrF" p (hackyStringIgnoreContext ns)
179+
showsUnaryWith showsPrec "NVStrF" p (principledStringIgnoreContext ns)
180180
NVList' lst -> showsUnaryWith (liftShowsPrec sp sl) "NVListF" p lst
181181
NVSet' attrs _ -> showsUnaryWith (liftShowsPrec sp sl) "NVSetF" p attrs
182182
NVPath' path -> showsUnaryWith showsPrec "NVPathF" p path

tests/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ ensureNixpkgsCanParse =
5959
time <- getCurrentTime
6060
runWithBasicEffectsIO (defaultOptions time) $
6161
Nix.nixEvalExprLoc Nothing expr
62-
let dir = hackyStringIgnoreContext ns
62+
let dir = principledStringIgnoreContext ns
6363
exists <- fileExist (unpack dir)
6464
unless exists $
6565
errorWithoutStackTrace $

0 commit comments

Comments
 (0)