Skip to content

Commit 70426e4

Browse files
committed
String: unflip StringContext
1 parent 12816f6 commit 70426e4

File tree

6 files changed

+22
-23
lines changed

6 files changed

+22
-23
lines changed

src/Nix/Builtins.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1139,7 +1139,7 @@ toFileNix name s =
11391139

11401140
let
11411141
storepath = coerce (fromString @Text) mres
1142-
sc = StringContext storepath DirectPath
1142+
sc = StringContext DirectPath storepath
11431143

11441144
toValue $ mkNixStringWithSingletonContext storepath sc
11451145

src/Nix/Convert.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -218,7 +218,7 @@ instance ( Convertible e t f m
218218
\case
219219
NVStr' ns -> pure $ pure ns
220220
NVPath' p ->
221-
(\path -> pure $ (`mkNixStringWithSingletonContext` (`StringContext` DirectPath) path) path ) . fromString . coerce <$>
221+
(\path -> pure $ (`mkNixStringWithSingletonContext` StringContext DirectPath path) path ) . fromString . coerce <$>
222222
addPath p
223223
NVSet' _ s ->
224224
maybe

src/Nix/Effects/Derivation.hs

Lines changed: 10 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -289,9 +289,9 @@ defaultDerivationStrict val = do
289289
let
290290
outputsWithContext =
291291
Map.mapWithKey
292-
(\out (coerce -> path) -> mkNixStringWithSingletonContext path $ StringContext drvPath $ DerivationOutput out)
292+
(\out (coerce -> path) -> mkNixStringWithSingletonContext path $ StringContext (DerivationOutput out) drvPath)
293293
(outputs drv')
294-
drvPathWithContext = mkNixStringWithSingletonContext drvPath $ StringContext drvPath AllOutputs
294+
drvPathWithContext = mkNixStringWithSingletonContext drvPath $ StringContext AllOutputs drvPath
295295
attrSet = mkNVStr <$> M.fromList (("drvPath", drvPathWithContext) : Map.toList outputsWithContext)
296296
-- TODO: Add location information for all the entries.
297297
-- here --v
@@ -309,13 +309,14 @@ defaultDerivationStrict val = do
309309
toStorePaths = foldl (flip addToInputs) mempty
310310

311311
addToInputs :: Bifunctor p => StringContext -> p (Set Text) (Map Text [Text]) -> p (Set Text) (Map Text [Text])
312-
addToInputs (StringContext (coerce -> path) kind) = case kind of
313-
DirectPath -> first $ Set.insert path
314-
DerivationOutput o -> second $ Map.insertWith (<>) path $ one o
315-
AllOutputs ->
316-
-- TODO: recursive lookup. See prim_derivationStrict
317-
-- XXX: When is this really used ?
318-
error "Not implemented: derivations depending on a .drv file are not yet supported."
312+
addToInputs (StringContext kind (coerce -> path)) =
313+
case kind of
314+
DirectPath -> first $ Set.insert path
315+
DerivationOutput o -> second $ Map.insertWith (<>) path $ one o
316+
AllOutputs ->
317+
-- TODO: recursive lookup. See prim_derivationStrict
318+
-- XXX: When is this really used ?
319+
error "Not implemented: derivations depending on a .drv file are not yet supported."
319320

320321

321322
-- | Build a derivation in a context collecting string contexts.

src/Nix/Json.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ toJSON = \case
7272
NVPath p ->
7373
do
7474
fp <- lift $ coerce <$> addPath p
75-
addSingletonStringContext $ StringContext (fromString fp) DirectPath
75+
addSingletonStringContext $ StringContext DirectPath $ fromString fp
7676
pure $ A.toJSON fp
7777
v -> lift $ throwError $ CoercionToJson v
7878

src/Nix/String.hs

Lines changed: 8 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -45,12 +45,11 @@ import Nix.Expr.Types ( VarName(..)
4545

4646
-- ** Context
4747

48-
-- 2021-07-18: NOTE: it should be ContextFlavor -> Varname.
4948
-- | A Nix 'StringContext' ...
5049
data StringContext =
5150
StringContext
52-
{ scPath :: !VarName
53-
, scFlavor :: !ContextFlavor
51+
{ scFlavor :: !ContextFlavor
52+
, scPath :: !VarName
5453
}
5554
deriving (Eq, Ord, Show, Generic)
5655

@@ -153,7 +152,7 @@ getContext = nsContext
153152

154153
fromNixLikeContext :: NixLikeContext -> S.HashSet StringContext
155154
fromNixLikeContext =
156-
S.fromList . (toStringContexts <=< (M.toList . getNixLikeContext))
155+
S.fromList . (uncurry toStringContexts <=< M.toList . getNixLikeContext)
157156

158157
-- | Extract the string contents from a NixString that has no context
159158
getStringNoContext :: NixString -> Maybe Text
@@ -176,9 +175,8 @@ extractNixString (NixString s c) =
176175

177176
-- this really should be 2 args, then with @toStringContexts path@ laziness it would tail recurse.
178177
-- for now tuple dissected internaly with laziness preservation.
179-
toStringContexts :: (VarName, NixLikeContextValue) -> [StringContext]
180-
toStringContexts ~(path, nlcv) =
181-
go nlcv
178+
toStringContexts :: VarName -> NixLikeContextValue -> [StringContext]
179+
toStringContexts path = go
182180
where
183181
go :: NixLikeContextValue -> [StringContext]
184182
go cv =
@@ -192,10 +190,10 @@ toStringContexts ~(path, nlcv) =
192190
_ -> mempty
193191
where
194192
mkCtxFor :: ContextFlavor -> StringContext
195-
mkCtxFor = StringContext path
196-
193+
mkCtxFor context = StringContext context path
197194
mkLstCtxFor :: ContextFlavor -> NixLikeContextValue -> [StringContext]
198-
mkLstCtxFor t c = mkCtxFor t : go c
195+
mkLstCtxFor t c = one (mkCtxFor t) <> go c
196+
199197

200198
toNixLikeContextValue :: StringContext -> (VarName, NixLikeContextValue)
201199
toNixLikeContextValue sc =

src/Nix/String/Coerce.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -134,4 +134,4 @@ coercePathToNixString =
134134
where
135135
storePathToNixString :: StorePath -> NixString
136136
storePathToNixString =
137-
(mkNixStringWithSingletonContext <*> (`StringContext` DirectPath)) . fromString . coerce
137+
(mkNixStringWithSingletonContext <*> StringContext DirectPath) . fromString . coerce

0 commit comments

Comments
 (0)