Skip to content

Commit 188c777

Browse files
Merge #980: String: (make -> mk) renames; other optimizations
* `String`: reduce (make -> mk) for the sake of unification of maker names it is around #406, but the topic needs work. * `Effects`: `class MonadEffects`: `(make -> to)AbsolutePath` * `Standard`: `{StdCited, StdThunk}` rm newtype accessor * noticed that `Standard`: `instance MonadValue (StdValue m) m` recurses on itself, so closed the recursion * `Expr`: `Types`: `TH.Lift NExpr`: TH 2.17: fx `liftTyped` * `Eval`: `evalSelect`: `extract`: one of the most used functions, so optimizing it a bit
2 parents b55ed28 + 77d148b commit 188c777

File tree

15 files changed

+118
-92
lines changed

15 files changed

+118
-92
lines changed

src/Nix/Builtins.hs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -351,7 +351,7 @@ data FileType
351351

352352
instance Convertible e t f m => ToValue FileType m (NValue t f m) where
353353
toValue =
354-
toValue . makeNixStringWithoutContext .
354+
toValue . mkNixStringWithoutContext .
355355
\case
356356
FileTypeRegular -> "regular" :: Text
357357
FileTypeDirectory -> "directory"
@@ -654,7 +654,7 @@ matchNix pat str =
654654
mkMatch t =
655655
bool
656656
(toValue ()) -- Shorthand for Null
657-
(toValue $ makeNixStringWithoutContext t)
657+
(toValue $ mkNixStringWithoutContext t)
658658
(not $ Text.null t)
659659

660660
case matchOnceText re s of
@@ -710,7 +710,7 @@ attrNamesNix
710710
:: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m)
711711
attrNamesNix =
712712
coersion . inHask @(AttrSet (NValue t f m))
713-
(fmap (makeNixStringWithoutContext . coerce) . sort . M.keys)
713+
(fmap (mkNixStringWithoutContext . coerce) . sort . M.keys)
714714
where
715715
coersion = fmap (coerce :: CoerceDeeperToNValue t f m)
716716

@@ -862,7 +862,7 @@ dirOfNix nvdir =
862862
unsafeDiscardStringContextNix
863863
:: MonadNix e t f m => NValue t f m -> m (NValue t f m)
864864
unsafeDiscardStringContextNix =
865-
inHask (makeNixStringWithoutContext . stringIgnoreContext)
865+
inHask (mkNixStringWithoutContext . stringIgnoreContext)
866866

867867
-- | Evaluate `a` to WHNF to collect its topmost effect.
868868
seqNix
@@ -1022,7 +1022,7 @@ replaceStringsNix tfrom tto ts =
10221022

10231023
-- 2021-02-18: NOTE: rly?: toStrict . toLazyText
10241024
-- Maybe `text-builder`, `text-show`?
1025-
finish ctx output = makeNixString (toStrict $ Builder.toLazyText output) ctx
1025+
finish ctx output = mkNixString (toStrict $ Builder.toLazyText output) ctx
10261026

10271027
replace (key, replacementNS, unprocessedInput) = replaceWithNixBug unprocessedInput updatedOutput
10281028

@@ -1120,7 +1120,7 @@ toFileNix name s =
11201120
t = coerce $ toText @FilePath $ coerce mres
11211121
sc = StringContext t DirectPath
11221122

1123-
toValue $ makeNixStringWithSingletonContext t sc
1123+
toValue $ mkNixStringWithSingletonContext t sc
11241124

11251125
toPathNix :: MonadNix e t f m => NValue t f m -> m (NValue t f m)
11261126
toPathNix = toValue @Path <=< fromValue @Path
@@ -1273,7 +1273,7 @@ scopedImportNix asetArg pathArg =
12731273

12741274
getEnvNix :: MonadNix e t f m => NValue t f m -> m (NValue t f m)
12751275
getEnvNix v =
1276-
(toValue . makeNixStringWithoutContext . fromMaybe mempty) =<< getEnvVar =<< fromStringNoContext =<< fromValue v
1276+
(toValue . mkNixStringWithoutContext . fromMaybe mempty) =<< getEnvVar =<< fromStringNoContext =<< fromValue v
12771277

12781278
sortNix
12791279
:: MonadNix e t f m
@@ -1405,11 +1405,11 @@ placeHolderNix p =
14051405
t <- fromStringNoContext =<< fromValue p
14061406
h <-
14071407
coerce @(Prim m NixString) @(m NixString) $
1408-
(hashStringNix `on` makeNixStringWithoutContext)
1408+
(hashStringNix `on` mkNixStringWithoutContext)
14091409
"sha256"
14101410
("nix-output:" <> t)
14111411
toValue
1412-
$ makeNixStringWithoutContext
1412+
$ mkNixStringWithoutContext
14131413
$ Text.cons '/'
14141414
$ Base32.encode
14151415
-- Please, stop Text -> Bytestring here after migration to Text
@@ -1540,7 +1540,7 @@ typeOfNix nvv =
15401540
NVBuiltin _ _ -> "lambda"
15411541
_ -> error "Pattern synonyms obscure complete patterns"
15421542

1543-
toValue $ makeNixStringWithoutContext detectType
1543+
toValue $ mkNixStringWithoutContext detectType
15441544

15451545
tryEvalNix
15461546
:: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m)
@@ -1736,7 +1736,7 @@ appendContextNix tx ty =
17361736
_x -> throwError $ ErrorCall $ "Invalid types for context value in builtins.appendContext: " <> show _x
17371737

17381738
addContext ns newContextValues =
1739-
makeNixString
1739+
mkNixString
17401740
(stringIgnoreContext ns)
17411741
(fromNixLikeContext $
17421742
NixLikeContext $
@@ -1750,7 +1750,7 @@ appendContextNix tx ty =
17501750
)
17511751

17521752
nixVersionNix :: MonadNix e t f m => m (NValue t f m)
1753-
nixVersionNix = toValue $ makeNixStringWithoutContext "2.3"
1753+
nixVersionNix = toValue $ mkNixStringWithoutContext "2.3"
17541754

17551755
langVersionNix :: MonadNix e t f m => m (NValue t f m)
17561756
langVersionNix = toValue (5 :: Int)

src/Nix/Convert.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -210,7 +210,7 @@ instance ( Convertible e t f m
210210
\case
211211
NVStr' ns -> pure $ pure ns
212212
NVPath' p ->
213-
(\path -> pure $ makeNixStringWithSingletonContext path (StringContext path DirectPath)) . fromString . coerce <$>
213+
(\path -> pure $ mkNixStringWithSingletonContext path (StringContext path DirectPath)) . fromString . coerce <$>
214214
addPath p
215215
NVSet' _ s ->
216216
maybe
@@ -373,7 +373,7 @@ instance Convertible e t f m
373373

374374
instance Convertible e t f m
375375
=> ToValue ByteString m (NValue' t f m (NValue t f m)) where
376-
toValue = pure . nvStr' . makeNixStringWithoutContext . decodeUtf8
376+
toValue = pure . nvStr' . mkNixStringWithoutContext . decodeUtf8
377377

378378
instance Convertible e t f m
379379
=> ToValue Path m (NValue' t f m (NValue t f m)) where
@@ -387,7 +387,7 @@ instance ( Convertible e t f m
387387
)
388388
=> ToValue SourcePos m (NValue' t f m (NValue t f m)) where
389389
toValue (SourcePos f l c) = do
390-
f' <- toValue $ makeNixStringWithoutContext $ toText f
390+
f' <- toValue $ mkNixStringWithoutContext $ toText f
391391
l' <- toValue $ unPos l
392392
c' <- toValue $ unPos c
393393
let pos = M.fromList [("file" :: VarName, f'), ("line", l'), ("column", c')]
@@ -439,7 +439,7 @@ instance Convertible e t f m
439439
allOutputs <- g nlcvAllOutputs
440440
outputs <- do
441441
let
442-
outputs = makeNixStringWithoutContext <$> nlcvOutputs nlcv
442+
outputs = mkNixStringWithoutContext <$> nlcvOutputs nlcv
443443

444444
ts :: [NValue t f m] <- traverse toValue outputs
445445
list

src/Nix/Effects.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -61,12 +61,11 @@ class
6161
)
6262
=> MonadEffects t f m where
6363

64-
-- | Determine the absolute path of relative path in the current context
65-
makeAbsolutePath :: Path -> m Path
64+
-- | Determine the absolute path in the current context.
65+
toAbsolutePath :: Path -> m Path
6666
findEnvPath :: String -> m Path
6767

68-
-- | Having an explicit list of sets corresponding to the NIX_PATH
69-
-- and a file path try to find an existing path
68+
-- | Having an explicit list of sets corresponding to the @NIX_PATH@ and a file path try to find an existing path.
7069
findPath :: [NValue t f m] -> Path -> m Path
7170

7271
importPath :: Path -> m (NValue t f m)

src/Nix/Effects/Basic.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -34,8 +34,8 @@ import Nix.Value.Monad
3434
import GHC.DataSize
3535
#endif
3636

37-
defaultMakeAbsolutePath :: MonadNix e t f m => Path -> m Path
38-
defaultMakeAbsolutePath origPath = do
37+
defaultToAbsolutePath :: MonadNix e t f m => Path -> m Path
38+
defaultToAbsolutePath origPath = do
3939
origPathExpanded <- expandHomePath origPath
4040
absPath <-
4141
bool
@@ -102,12 +102,12 @@ findEnvPathM name = do
102102
where
103103
nixFilePath :: MonadEffects t f m => Path -> m (Maybe Path)
104104
nixFilePath path = do
105-
absPath <- makeAbsolutePath @t @f path
105+
absPath <- toAbsolutePath @t @f path
106106
isDir <- doesDirectoryExist absPath
107107
absFile <-
108108
bool
109109
(pure absPath)
110-
(makeAbsolutePath @t @f $ coerce $ (coerce absPath) </> "default.nix")
110+
(toAbsolutePath @t @f $ coerce $ (coerce absPath) </> "default.nix")
111111
isDir
112112
exists <- doesFileExist absFile
113113
pure $
@@ -232,7 +232,7 @@ findPathM = findPathBy existingPath
232232
existingPath :: MonadEffects t f m => Path -> m (Maybe Path)
233233
existingPath path =
234234
do
235-
apath <- makeAbsolutePath @t @f path
235+
apath <- toAbsolutePath @t @f path
236236
doesExist <- doesPathExist apath
237237
pure $ pure apath `whenTrue` doesExist
238238

src/Nix/Effects/Derivation.hs

Lines changed: 2 additions & 2 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) -> makeNixStringWithSingletonContext path $ StringContext drvPath $ DerivationOutput out)
292+
(\out (coerce -> path) -> mkNixStringWithSingletonContext path $ StringContext drvPath $ DerivationOutput out)
293293
(outputs drv')
294-
drvPathWithContext = makeNixStringWithSingletonContext drvPath $ StringContext drvPath AllOutputs
294+
drvPathWithContext = mkNixStringWithSingletonContext drvPath $ StringContext drvPath AllOutputs
295295
attrSet = nvStr <$> M.fromList (("drvPath", drvPathWithContext) : Map.toList outputsWithContext)
296296
-- TODO: Add location information for all the entries.
297297
-- here --v

src/Nix/Eval.hs

Lines changed: 18 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -407,25 +407,28 @@ evalSelect aset attr =
407407
s <- aset
408408
path <- traverse evalGetterKeyName attr
409409

410-
extract s path
410+
extract path s
411411

412412
where
413-
extract :: v -> NonEmpty VarName -> m (Either (v, NonEmpty VarName) (m v))
414-
extract x path@(k :| ks) =
413+
extract :: NonEmpty VarName -> v -> m (Either (v, NonEmpty VarName) (m v))
414+
extract path@(k :| ks) x =
415415
do
416416
x' <- fromValueMay x
417417

418-
case x' of
419-
Nothing -> pure $ Left (x, path)
420-
Just (s :: AttrSet v, p :: PositionSet)
421-
| Just t <- M.lookup k s ->
422-
do
423-
list
424-
(pure . pure)
425-
(\ (y : ys) -> ((`extract` (y :| ys)) =<<))
426-
ks
427-
$ demand t
428-
| otherwise -> Left . (, path) <$> toValue (s, p)
418+
maybe
419+
(pure $ Left (x, path))
420+
(\ (s :: AttrSet v, _ :: PositionSet) ->
421+
maybe
422+
(pure $ Left (x, path))
423+
(list
424+
(pure . pure)
425+
(\ (y : ys) -> ((extract (y :| ys)) =<<))
426+
ks
427+
. demand
428+
)
429+
((`M.lookup` s) k)
430+
)
431+
x'
429432

430433
-- | Evaluate a component of an attribute path in a context where we are
431434
-- *retrieving* a value
@@ -466,7 +469,7 @@ assembleString = fromParts . stringParts
466469
go =
467470
runAntiquoted
468471
"\n"
469-
(pure . pure . makeNixStringWithoutContext)
472+
(pure . pure . mkNixStringWithoutContext)
470473
(fromValueMay =<<)
471474

472475
buildArgument

src/Nix/Exec.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -212,7 +212,7 @@ instance MonadNix e t f m => MonadEval (NValue t f m) m where
212212
scope <- currentScopes
213213
span <- currentPos
214214
nvPathP (Provenance scope $ NLiteralPathAnnF span p) <$>
215-
makeAbsolutePath @t @f @m p
215+
toAbsolutePath @t @f @m p
216216

217217
evalEnvPath p = do
218218
scope <- currentScopes
@@ -422,10 +422,10 @@ execBinaryOpForced scope span op lval rval = case op of
422422
(throwError $ ErrorCall "A string that refers to a store path cannot be appended to a path.") -- data/nix/src/libexpr/eval.cc:1412
423423
(\ rs2 ->
424424
nvPathP prov <$>
425-
makeAbsolutePath @t @f (ls <> (coerce $ toString rs2))
425+
toAbsolutePath @t @f (ls <> (coerce $ toString rs2))
426426
)
427427
(getStringNoContext rs)
428-
(NVPath ls, NVPath rs) -> nvPathP prov <$> makeAbsolutePath @t @f (ls <> rs)
428+
(NVPath ls, NVPath rs) -> nvPathP prov <$> toAbsolutePath @t @f (ls <> rs)
429429

430430
(ls@NVSet{}, NVStr rs) ->
431431
(\ls2 -> nvStrP prov (ls2 <> rs)) <$>

src/Nix/Expr/Types.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -631,7 +631,7 @@ instance TH.Lift NExpr where
631631
pure [| $(TH.lift b) |]
632632
)
633633
#if MIN_VERSION_template_haskell(2,17,0)
634-
liftTyped = TH.liftTyped
634+
liftTyped = TH.unsafeCodeCoerce . TH.lift
635635
#elif MIN_VERSION_template_haskell(2,16,0)
636636
liftTyped = TH.unsafeTExpCoerce . TH.lift
637637
#endif
@@ -677,12 +677,12 @@ stripPositionInfo = transport phi
677677
where
678678
transport f (Fix x) = Fix $ transport f <$> f x
679679

680-
phi (NSet recur binds) = NSet recur $ go <$> binds
681-
phi (NLet binds body) = NLet (go <$> binds) body
680+
phi (NSet recur binds) = NSet recur $ erasePositions <$> binds
681+
phi (NLet binds body) = NLet (erasePositions <$> binds) body
682682
phi x = x
683683

684-
go (NamedVar path r _pos) = NamedVar path r nullPos
685-
go (Inherit ms names _pos) = Inherit ms names nullPos
684+
erasePositions (NamedVar path r _pos) = NamedVar path r nullPos
685+
erasePositions (Inherit ms names _pos) = Inherit ms names nullPos
686686

687687
nullPos :: SourcePos
688688
nullPos = on (SourcePos "<string>") mkPos 1 1

src/Nix/Frames.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -30,12 +30,12 @@ import Nix.Utils ( Has(..)
3030
)
3131

3232
data NixLevel = Fatal | Error | Warning | Info | Debug
33-
deriving (Ord, Eq, Bounded, Enum, Show)
33+
deriving (Ord, Eq, Bounded, Enum, Show)
3434

3535
data NixFrame = NixFrame
36-
{ frameLevel :: NixLevel
37-
, frame :: SomeException
38-
}
36+
{ frameLevel :: NixLevel
37+
, frame :: SomeException
38+
}
3939

4040
instance Show NixFrame where
4141
show (NixFrame level f) =
@@ -46,7 +46,7 @@ type Frames = [NixFrame]
4646
type Framed e m = (MonadReader e m, Has e Frames, MonadThrow m)
4747

4848
newtype NixException = NixException Frames
49-
deriving Show
49+
deriving Show
5050

5151
instance Exception NixException
5252

src/Nix/Fresh/Basic.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ instance MonadExec m => MonadExec (StdIdT m)
2929

3030
instance (MonadEffects t f m, MonadDataContext f m)
3131
=> MonadEffects t f (StdIdT m) where
32-
makeAbsolutePath = lift . makeAbsolutePath @t @f @m
32+
toAbsolutePath = lift . toAbsolutePath @t @f @m
3333
findEnvPath = lift . findEnvPath @t @f @m
3434
findPath vs path = do
3535
i <- FreshIdT ask

0 commit comments

Comments
 (0)