@@ -60,9 +60,9 @@ class (Show v, Monad m) => MonadEval v m where
6060 evalListElem :: [m v] -> Int -> m v -> m v
6161 evalList :: [v] -> m v
6262 evalSetElem :: AttrSet (m v) -> Text -> m v -> m v
63- evalSet :: AttrSet v -> KeyMap SourcePos -> m v
63+ evalSet :: AttrSet v -> PositionSet -> m v
6464 evalRecSetElem :: AttrSet (m v) -> Text -> m v -> m v
65- evalRecSet :: AttrSet v -> KeyMap SourcePos -> m v
65+ evalRecSet :: AttrSet v -> PositionSet -> m v
6666 evalLetElem :: Text -> m v -> m v
6767 evalLet :: m v -> m v
6868-}
@@ -76,8 +76,8 @@ type MonadNixEval v m
7676 , ToValue Bool m v
7777 , ToValue [v ] m v
7878 , FromValue NixString m v
79- , ToValue (AttrSet v , KeyMap SourcePos ) m v
80- , FromValue (AttrSet v , KeyMap SourcePos ) m v
79+ , ToValue (AttrSet v , PositionSet ) m v
80+ , FromValue (AttrSet v , PositionSet ) m v
8181 )
8282
8383data EvalFrame m v
@@ -209,7 +209,7 @@ evalWithAttrSet aset body = do
209209 -- sure the action it evaluates is to force a thunk, so its value is only
210210 -- computed once.
211211 deferredAset <- defer $ withScopes scope aset
212- let attrSet = fst <$> (fromValue @ (AttrSet v , KeyMap SourcePos ) =<< demand deferredAset)
212+ let attrSet = fst <$> (fromValue @ (AttrSet v , PositionSet ) =<< demand deferredAset)
213213
214214 pushWeakScope attrSet body
215215
@@ -219,9 +219,9 @@ attrSetAlter
219219 => [VarName ]
220220 -> SourcePos
221221 -> AttrSet (m v )
222- -> KeyMap SourcePos
222+ -> PositionSet
223223 -> m v
224- -> m (AttrSet (m v ), KeyMap SourcePos )
224+ -> m (AttrSet (m v ), PositionSet )
225225attrSetAlter [] _ _ _ _ = evalError @ v $ ErrorCall " invalid selector with no components"
226226attrSetAlter (k : ks) pos m p val =
227227 bool
@@ -230,7 +230,7 @@ attrSetAlter (k : ks) pos m p val =
230230 (recurse mempty mempty )
231231 (\ x ->
232232 do
233- (st, sp) <- fromValue @ (AttrSet v , KeyMap SourcePos ) =<< x
233+ (st, sp) <- fromValue @ (AttrSet v , PositionSet ) =<< x
234234 recurse (demand <$> st) sp
235235 )
236236 (M. lookup k m)
@@ -243,7 +243,7 @@ attrSetAlter (k : ks) pos m p val =
243243 (\ (st', _) ->
244244 (M. insert
245245 k
246- (toValue @ (AttrSet v , KeyMap SourcePos ) =<< (, mempty ) <$> sequence st')
246+ (toValue @ (AttrSet v , PositionSet ) =<< (, mempty ) <$> sequence st')
247247 m
248248 , M. insert (coerce k) pos p
249249 )
@@ -293,7 +293,7 @@ evalBinds
293293 . MonadNixEval v m
294294 => Bool
295295 -> [Binding (m v )]
296- -> m (AttrSet v , KeyMap SourcePos )
296+ -> m (AttrSet v , PositionSet )
297297evalBinds recursive binds =
298298 do
299299 scope <- currentScopes :: m (Scopes m v )
@@ -304,7 +304,7 @@ evalBinds recursive binds =
304304 buildResult
305305 :: Scopes m v
306306 -> [([VarName ], SourcePos , m v )]
307- -> m (AttrSet v , KeyMap SourcePos )
307+ -> m (AttrSet v , PositionSet )
308308 buildResult scope bindings =
309309 do
310310 (s, p) <- foldM insert (mempty , mempty ) bindings
@@ -331,7 +331,7 @@ evalBinds recursive binds =
331331 pure $
332332 (\ (k, v) ->
333333 ( [k]
334- , fromMaybe pos $ M. lookup @ Text (coerce k) p'
334+ , fromMaybe pos $ M. lookup k p'
335335 , demand v
336336 )
337337 ) <$> M. toList o'
@@ -349,7 +349,7 @@ evalBinds recursive binds =
349349 processAttrSetKeys (h :| t) =
350350 maybe
351351 -- Empty attrset - return a stub.
352- (pure ( mempty , nullPos, toValue @ (AttrSet v , KeyMap SourcePos ) (mempty , mempty )) )
352+ (pure ( mempty , nullPos, toValue @ (AttrSet v , PositionSet ) (mempty , mempty )) )
353353 (\ k ->
354354 list
355355 -- No more keys in the attrset - return the result
@@ -387,7 +387,7 @@ evalBinds recursive binds =
387387 (withScopes scope $ lookupVar key)
388388 (\ s ->
389389 do
390- (attrset, _) <- fromValue @ (AttrSet v , KeyMap SourcePos ) =<< s
390+ (attrset, _) <- fromValue @ (AttrSet v , PositionSet ) =<< s
391391
392392 clearScopes @ v $ pushScope attrset $ lookupVar key
393393 )
@@ -423,7 +423,7 @@ evalSelect aset attr =
423423
424424 case x' of
425425 Nothing -> pure $ Left (x, path)
426- Just (s :: AttrSet v , p :: KeyMap SourcePos )
426+ Just (s :: AttrSet v , p :: PositionSet )
427427 | Just t <- M. lookup k s ->
428428 do
429429 list
@@ -490,7 +490,7 @@ buildArgument params arg =
490490 Param name -> M. singleton name <$> argThunk
491491 ParamSet s isVariadic m ->
492492 do
493- (args, _) <- fromValue @ (AttrSet v , KeyMap SourcePos ) =<< arg
493+ (args, _) <- fromValue @ (AttrSet v , PositionSet ) =<< arg
494494 let
495495 inject =
496496 maybe
0 commit comments