Skip to content

Commit 6ce83f9

Browse files
committed
String: reduce (make -> mk) for the sake of unification of maker names
1 parent b55ed28 commit 6ce83f9

File tree

7 files changed

+32
-32
lines changed

7 files changed

+32
-32
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/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: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -466,7 +466,7 @@ assembleString = fromParts . stringParts
466466
go =
467467
runAntiquoted
468468
"\n"
469-
(pure . pure . makeNixStringWithoutContext)
469+
(pure . pure . mkNixStringWithoutContext)
470470
(fromValueMay =<<)
471471

472472
buildArgument

src/Nix/String.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
module Nix.String
44
( NixString
55
, getContext
6-
, makeNixString
6+
, mkNixString
77
, StringContext(..)
88
, ContextFlavor(..)
99
, NixLikeContext(..)
@@ -14,8 +14,8 @@ module Nix.String
1414
, intercalateNixString
1515
, getStringNoContext
1616
, stringIgnoreContext
17-
, makeNixStringWithoutContext
18-
, makeNixStringWithSingletonContext
17+
, mkNixStringWithoutContext
18+
, mkNixStringWithSingletonContext
1919
, modifyNixContents
2020
, WithStringContext
2121
, WithStringContextT(..)
@@ -127,17 +127,17 @@ instance Hashable NixString
127127
-- ** Makers
128128

129129
-- | Constructs NixString without a context
130-
makeNixStringWithoutContext :: Text -> NixString
131-
makeNixStringWithoutContext = (`NixString` mempty)
130+
mkNixStringWithoutContext :: Text -> NixString
131+
mkNixStringWithoutContext = (`NixString` mempty)
132132

133133
-- | Create NixString using a singleton context
134-
makeNixStringWithSingletonContext
134+
mkNixStringWithSingletonContext
135135
:: VarName -> StringContext -> NixString
136-
makeNixStringWithSingletonContext s c = NixString (coerce @VarName @Text s) $ one c
136+
mkNixStringWithSingletonContext s c = NixString (coerce @VarName @Text s) $ one c
137137

138138
-- | Create NixString from a Text and context
139-
makeNixString :: Text -> S.HashSet StringContext -> NixString
140-
makeNixString = NixString
139+
mkNixString :: Text -> S.HashSet StringContext -> NixString
140+
mkNixString = NixString
141141

142142

143143
-- ** Checkers

src/Nix/String/Coerce.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -107,13 +107,13 @@ coerceToString call ctsm clevel = go
107107

108108
v -> err v
109109
err v = throwError $ ErrorCall $ "Expected a string, but saw: " <> show v
110-
castToNixString = pure . makeNixStringWithoutContext
110+
castToNixString = pure . mkNixStringWithoutContext
111111

112-
nixStringUnwords = intercalateNixString $ makeNixStringWithoutContext " "
112+
nixStringUnwords = intercalateNixString $ mkNixStringWithoutContext " "
113113

114114
storePathToNixString :: StorePath -> NixString
115115
storePathToNixString sp =
116-
makeNixStringWithSingletonContext
116+
mkNixStringWithSingletonContext
117117
t
118118
(StringContext t DirectPath)
119119
where

src/Nix/Value.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -600,7 +600,7 @@ nvStr = Free . nvStr'
600600
nvStrWithoutContext :: Applicative f
601601
=> Text
602602
-> NValue t f m
603-
nvStrWithoutContext = nvStr . makeNixStringWithoutContext
603+
nvStrWithoutContext = nvStr . mkNixStringWithoutContext
604604

605605

606606
-- | Life of a Haskell FilePath to the life of a Nix path

0 commit comments

Comments
 (0)