Skip to content

Commit 49d91c7

Browse files
committed
treewide: (toText -> fromString)
This explicitly states the code smell of String use left.
1 parent 28a5f69 commit 49d91c7

File tree

13 files changed

+27
-27
lines changed

13 files changed

+27
-27
lines changed

main/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -121,7 +121,7 @@ main' opts@Options{..} = runWithBasicEffectsIO opts execContentsFilesOrRepl
121121
either
122122
(\ err -> errorWithoutStackTrace $ "Type error: " <> ppShow err)
123123
(\ ty -> liftIO $ putStrLn $ "Type of expression: " <>
124-
ppShow (fromMaybe mempty $ Map.lookup @VarName @[Scheme] "it" $ coerce ty)
124+
ppShow (maybeToMonoid $ Map.lookup @VarName @[Scheme] "it" $ coerce ty)
125125
)
126126
(HM.inferTop mempty [("it", stripAnnotation expr')])
127127

main/Repl.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -68,7 +68,7 @@ main' iniVal =
6868
evalStateT
6969
(evalRepl
7070
banner
71-
(cmd . toText)
71+
(cmd . fromString)
7272
options
7373
(pure commandPrefix)
7474
(pure "paste")
@@ -125,7 +125,7 @@ main' iniVal =
125125
-> m ()
126126
optMatcher s [] _ = liftIO $ Text.putStrLn $ "No such command :" <> s
127127
optMatcher s ((x, m) : xs) args
128-
| s `Text.isPrefixOf` toText x = m $ toString args
128+
| s `Text.isPrefixOf` fromString x = m $ toString args
129129
| otherwise = optMatcher s xs args
130130

131131

@@ -392,7 +392,7 @@ completeFunc reversedPrev word
392392
listFiles word
393393

394394
-- Attributes of sets in REPL context
395-
| var : subFields <- Text.split (== '.') (toText word) , not $ null subFields =
395+
| var : subFields <- Text.split (== '.') (fromString word) , not $ null subFields =
396396
do
397397
state <- get
398398
maybe

src/Nix/Builtins.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -798,7 +798,7 @@ baseNameOfNix x =
798798
pure $
799799
nvStr $
800800
modifyNixContents
801-
(toText . takeFileName . toString)
801+
(fromString . takeFileName . toString)
802802
ns
803803

804804
bitAndNix
@@ -852,7 +852,7 @@ dirOfNix nvdir =
852852
dir <- demand nvdir
853853

854854
case dir of
855-
NVStr ns -> pure $ nvStr $ modifyNixContents (toText . takeDirectory . toString) ns
855+
NVStr ns -> pure $ nvStr $ modifyNixContents (fromString . takeDirectory . toString) ns
856856
NVPath path -> pure $ nvPath $ coerce $ takeDirectory $ coerce path
857857
v -> throwError $ ErrorCall $ "dirOf: expected string or path, got " <> show v
858858

@@ -1112,7 +1112,7 @@ toFileNix name s =
11121112
mres <-
11131113
toFile_
11141114
(coerce $ toString name')
1115-
(toString $ stringIgnoreContext s')
1115+
(stringIgnoreContext s')
11161116

11171117
let
11181118
t = coerce $ toText @FilePath $ coerce mres

src/Nix/Convert.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -399,7 +399,7 @@ instance ( Convertible e t f m
399399
)
400400
=> ToValue SourcePos m (NValue' t f m (NValue t f m)) where
401401
toValue (SourcePos f l c) = do
402-
f' <- toValue $ mkNixStringWithoutContext $ toText f
402+
f' <- toValue $ mkNixStringWithoutContext $ fromString f
403403
l' <- toValue $ unPos l
404404
c' <- toValue $ unPos c
405405
let pos = M.fromList [("file" :: VarName, f'), ("line", l'), ("column", c')]

src/Nix/Effects.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -137,7 +137,7 @@ instance MonadExec IO where
137137
(prog : args) -> do
138138
(exitCode, out, _) <- liftIO $ readProcessWithExitCode (toString prog) (toString <$> args) ""
139139
let
140-
t = Text.strip $ toText out
140+
t = Text.strip $ fromString out
141141
emsg = "program[" <> prog <> "] args=" <> show args
142142
case exitCode of
143143
ExitSuccess ->
@@ -194,7 +194,7 @@ instance MonadInstantiate IO where
194194
either
195195
(\ e -> Left $ ErrorCall $ "Error parsing output of nix-instantiate: " <> show e)
196196
pure
197-
(parseNixTextLoc $ toText out)
197+
(parseNixTextLoc $ fromString out)
198198
status -> Left $ ErrorCall $ "nix-instantiate failed: " <> show status <> ": " <> err
199199

200200
deriving
@@ -230,12 +230,12 @@ class
230230
-- ** Instances
231231

232232
instance MonadEnv IO where
233-
getEnvVar = (<<$>>) toText . lookupEnv . toString
233+
getEnvVar = (<<$>>) fromString . lookupEnv . toString
234234

235-
getCurrentSystemOS = pure $ toText System.Info.os
235+
getCurrentSystemOS = pure $ fromString System.Info.os
236236

237237
-- Invert the conversion done by GHC_CONVERT_CPU in GHC's aclocal.m4
238-
getCurrentSystemArch = pure $ toText $ case System.Info.arch of
238+
getCurrentSystemArch = pure $ fromString $ case System.Info.arch of
239239
"i386" -> "i686"
240240
arch -> arch
241241

@@ -438,7 +438,7 @@ addPath p =
438438
either
439439
throwError
440440
pure
441-
=<< addToStore (toText $ takeFileName (coerce p)) p True False
441+
=<< addToStore (fromString $ takeFileName (coerce p)) p True False
442442

443-
toFile_ :: (Framed e m, MonadStore m) => Path -> String -> m StorePath
444-
toFile_ p contents = addTextToStore (toText p) (toText contents) mempty False
443+
toFile_ :: (Framed e m, MonadStore m) => Path -> Text -> m StorePath
444+
toFile_ p contents = addTextToStore (toText p) contents mempty False

src/Nix/Effects/Derivation.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ writeDerivation drv@Derivation{inputs, name} = do
7676
let (inputSrcs, inputDrvs) = inputs
7777
references <- Set.fromList <$> traverse parsePath (Set.toList $ inputSrcs <> Set.fromList (Map.keys inputDrvs))
7878
path <- addTextToStore (Text.append name ".drv") (unparseDrv drv) (S.fromList $ Set.toList references) False
79-
parsePath $ toText @Path $ coerce path
79+
parsePath $ fromString $ coerce path
8080

8181
-- | Traverse the graph of inputDrvs to replace fixed output derivations with their fixed output hash.
8282
-- this avoids propagating changes to their .drv when the output hash stays the same.
@@ -206,7 +206,7 @@ derivationParser = do
206206
pure $ Derivation {inputs = (inputSrcs, inputDrvs), ..}
207207
where
208208
s :: Parsec () Text Text
209-
s = fmap toText $ string "\"" *> manyTill (escaped <|> regular) (string "\"")
209+
s = fmap fromString $ string "\"" *> manyTill (escaped <|> regular) (string "\"")
210210
escaped = char '\\' *>
211211
( '\n' <$ string "n"
212212
<|> '\r' <$ string "r"

src/Nix/Expr/Types.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -267,7 +267,7 @@ data NString r
267267
-- | For the the 'IsString' instance, we use a plain doublequoted string.
268268
instance IsString (NString r) where
269269
fromString "" = DoubleQuoted mempty
270-
fromString string = DoubleQuoted [Plain $ toText string]
270+
fromString string = DoubleQuoted [Plain $ fromString string]
271271

272272
$(deriveShow1 ''NString)
273273
$(deriveRead1 ''NString)

src/Nix/Expr/Types/Annotated.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -183,7 +183,7 @@ annNStr :: AnnUnit SrcSpan (NString NExprLoc) -> NExprLoc
183183
annNStr (AnnUnit s1 s) = NStrAnn s1 s
184184

185185
deltaInfo :: SourcePos -> (Text, Int, Int)
186-
deltaInfo (SourcePos fp l c) = (toText fp, unPos l, unPos c)
186+
deltaInfo (SourcePos fp l c) = (fromString fp, unPos l, unPos c)
187187

188188
annNNull :: NExprLoc
189189
annNNull = NConstantAnn nullSpan NNull

src/Nix/Parser.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -326,7 +326,7 @@ nixString' = label "string" $ lexeme $ doubleQuoted <|> indented
326326
antiquoted
327327
<|> Plain . one <$> char '$'
328328
<|> esc
329-
<|> Plain . toText <$> some plainChar
329+
<|> Plain . fromString <$> some plainChar
330330
where
331331
plainChar :: Parser Char
332332
plainChar =

src/Nix/Pretty.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -383,7 +383,7 @@ printNix = iterNValueByDiscardWith thk phi
383383
phi :: NValue' t f m String -> String
384384
phi (NVConstant' a ) = toString $ atomText a
385385
phi (NVStr' ns) = show $ stringIgnoreContext ns
386-
phi (NVList' l ) = toString $ "[ " <> unwords (fmap toText l) <> " ]"
386+
phi (NVList' l ) = toString $ "[ " <> unwords (fmap fromString l) <> " ]"
387387
phi (NVSet' _ s) =
388388
"{ " <>
389389
concat

0 commit comments

Comments
 (0)