Skip to content

Commit 9c4b44e

Browse files
committed
upd remaining ((++) -> (<>))
1 parent 1939be1 commit 9c4b44e

File tree

9 files changed

+69
-69
lines changed

9 files changed

+69
-69
lines changed

main/Main.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -77,14 +77,14 @@ main = do
7777
else errorWithoutStackTrace
7878
)
7979
$ "Parse failed: "
80-
++ show err
80+
<> show err
8181

8282
Success expr -> do
8383
when (check opts) $ do
8484
expr' <- liftIO (reduceExpr mpath expr)
8585
case HM.inferTop Env.empty [("it", stripAnnotation expr')] of
86-
Left err -> errorWithoutStackTrace $ "Type error: " ++ PS.ppShow err
87-
Right ty -> liftIO $ putStrLn $ "Type of expression: " ++ PS.ppShow
86+
Left err -> errorWithoutStackTrace $ "Type error: " <> PS.ppShow err
87+
Right ty -> liftIO $ putStrLn $ "Type of expression: " <> PS.ppShow
8888
(fromJust (Map.lookup "it" (Env.types ty)))
8989

9090
-- liftIO $ putStrLn $ runST $
@@ -167,7 +167,7 @@ main = do
167167
xs <- forM (sortOn fst (M.toList s)) $ \(k, nv) -> case nv of
168168
Free v -> pure (k, Just (Free v))
169169
Pure (StdThunk (extract -> Thunk _ _ ref)) -> do
170-
let path = prefix ++ Text.unpack k
170+
let path = prefix <> Text.unpack k
171171
(_, descend) = filterEntry path k
172172
val <- readVar @(StandardT (StdIdT IO)) ref
173173
case val of
@@ -176,14 +176,14 @@ main = do
176176
| otherwise -> pure (k, Nothing)
177177

178178
forM_ xs $ \(k, mv) -> do
179-
let path = prefix ++ Text.unpack k
179+
let path = prefix <> Text.unpack k
180180
(report, descend) = filterEntry path k
181181
when report $ do
182182
liftIO $ putStrLn path
183183
when descend $ case mv of
184184
Nothing -> pure ()
185185
Just v -> case v of
186-
NVSet s' _ -> go (path ++ ".") s'
186+
NVSet s' _ -> go (path <> ".") s'
187187
_ -> pure ()
188188
where
189189
filterEntry path k = case (path, k) of
@@ -207,9 +207,9 @@ main = do
207207
catch (Just <$> demand v pure) $ \(NixException frames) -> do
208208
liftIO
209209
. putStrLn
210-
. ("Exception forcing " ++)
211-
. (k ++)
212-
. (": " ++)
210+
. ("Exception forcing " <>)
211+
. (k <>)
212+
. (": " <>)
213213
. show
214214
=<< renderFrames @(StdValue (StandardT (StdIdT IO)))
215215
@(StdThunk (StandardT (StdIdT IO)))
@@ -228,7 +228,7 @@ main = do
228228
-> m (NValue t f m)
229229
handleReduced path (expr', eres) = do
230230
liftIO $ do
231-
putStrLn $ "Wrote winnowed expression tree to " ++ path
231+
putStrLn $ "Wrote winnowed expression tree to " <> path
232232
writeFile path $ show $ prettyNix (stripAnnotation expr')
233233
case eres of
234234
Left err -> throwM err

main/Repl.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -119,7 +119,7 @@ main' iniVal = initState iniVal >>= \s -> flip evalStateT s
119119
-> System.Console.Repline.Options m
120120
-> String
121121
-> m ()
122-
optMatcher s [] _ = liftIO $ putStrLn $ "No such command :" ++ s
122+
optMatcher s [] _ = liftIO $ putStrLn $ "No such command :" <> s
123123
optMatcher s ((x, m) : xs) args
124124
| s `Data.List.isPrefixOf` x = m args
125125
| otherwise = optMatcher s xs args
@@ -166,7 +166,7 @@ initState mIni = do
166166
where
167167
evalText :: (MonadNix e t f m) => Text -> m (NValue t f m)
168168
evalText expr = case parseNixTextLoc expr of
169-
Failure e -> error $ "Impossible happened: Unable to parse expression - '" ++ Data.Text.unpack expr ++ "' error was " ++ show e
169+
Failure e -> error $ "Impossible happened: Unable to parse expression - '" <> Data.Text.unpack expr <> "' error was " <> show e
170170
Success e -> do evalExprLoc e
171171

172172
type Repl e t f m = HaskelineT (StateT (IState t f m) m)

src/Nix.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,7 @@ evaluateExpression
107107
-> m a
108108
evaluateExpression mpath evaluator handler expr = do
109109
opts :: Options <- asks (view hasLens)
110-
args <- traverse (traverse eval') $ fmap (second parseArg) (arg opts) ++ fmap
110+
args <- traverse (traverse eval') $ fmap (second parseArg) (arg opts) <> fmap
111111
(second mkStr)
112112
(argstr opts)
113113
evaluator mpath expr >>= \f -> demand f $ \f' ->
@@ -144,22 +144,22 @@ processResult h val = do
144144
_ ->
145145
errorWithoutStackTrace
146146
$ "Expected a list for selector '"
147-
++ show n
148-
++ "', but got: "
149-
++ show v
147+
<> show n
148+
<> "', but got: "
149+
<> show v
150150
go (k : ks) v = demand v $ \case
151151
NVSet xs _ -> case M.lookup k xs of
152152
Nothing ->
153153
errorWithoutStackTrace
154154
$ "Set does not contain key '"
155-
++ Text.unpack k
156-
++ "'"
155+
<> Text.unpack k
156+
<> "'"
157157
Just v' -> case ks of
158158
[] -> h v'
159159
_ -> go ks v'
160160
_ ->
161161
errorWithoutStackTrace
162162
$ "Expected a set for selector '"
163-
++ Text.unpack k
164-
++ "', but got: "
165-
++ show v
163+
<> Text.unpack k
164+
<> "', but got: "
165+
<> show v

tests/Main.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ ensureLangTestsPresent = do
4242
errorWithoutStackTrace $ unlines
4343
[ "Directory data/nix does not have any files."
4444
, "Did you forget to run"
45-
++ " \"git submodule update --init --recursive\"?" ]
45+
<> " \"git submodule update --init --recursive\"?" ]
4646

4747
ensureNixpkgsCanParse :: Assertion
4848
ensureNixpkgsCanParse =
@@ -63,27 +63,27 @@ ensureNixpkgsCanParse =
6363
exists <- fileExist (unpack dir)
6464
unless exists $
6565
errorWithoutStackTrace $
66-
"Directory " ++ show dir ++ " does not exist"
66+
"Directory " <> show dir <> " does not exist"
6767
files <- globDir1 (compile "**/*.nix") (unpack dir)
6868
when (null files) $
6969
errorWithoutStackTrace $
70-
"Directory " ++ show dir ++ " does not have any files"
70+
"Directory " <> show dir <> " does not have any files"
7171
forM_ files $ \file -> do
7272
unless ("azure-cli/default.nix" `isSuffixOf` file ||
7373
"os-specific/linux/udisks/2-default.nix" `isSuffixOf` file) $ do
7474
-- Parse and deepseq the resulting expression tree, to ensure the
7575
-- parser is fully executed.
7676
_ <- consider file (parseNixFileLoc file) $ Exc.evaluate . force
7777
pure ()
78-
v -> error $ "Unexpected parse from default.nix: " ++ show v
78+
v -> error $ "Unexpected parse from default.nix: " <> show v
7979
where
8080
getExpr k m = let Just (Just r) = lookup k m in r
8181
getString k m =
8282
let Fix (NStr (DoubleQuoted [Plain str])) = getExpr k m in str
8383

8484
consider path action k = action >>= \case
8585
Failure err -> errorWithoutStackTrace $
86-
"Parsing " ++ path ++ " failed: " ++ show err
86+
"Parsing " <> path <> " failed: " <> show err
8787
Success expr -> k expr
8888

8989
main :: IO ()
@@ -95,18 +95,18 @@ main = do
9595
prettyTestsEnv <- lookupEnv "PRETTY_TESTS"
9696

9797
pwd <- getCurrentDirectory
98-
setEnv "NIX_REMOTE" (pwd ++ "/real-store")
99-
setEnv "NIX_DATA_DIR" (pwd ++ "/data")
98+
setEnv "NIX_REMOTE" (pwd <> "/real-store")
99+
setEnv "NIX_DATA_DIR" (pwd <> "/data")
100100

101101
defaultMain $ testGroup "hnix" $
102102
[ ParserTests.tests
103103
, EvalTests.tests
104104
, PrettyTests.tests
105-
, ReduceExprTests.tests] ++
105+
, ReduceExprTests.tests] <>
106106
[ PrettyParseTests.tests
107-
(fromIntegral (read (fromMaybe "0" prettyTestsEnv) :: Int)) ] ++
108-
[ evalComparisonTests ] ++
107+
(fromIntegral (read (fromMaybe "0" prettyTestsEnv) :: Int)) ] <>
108+
[ evalComparisonTests ] <>
109109
[ testCase "Nix language tests present" ensureLangTestsPresent
110-
, nixLanguageTests ] ++
110+
, nixLanguageTests ] <>
111111
[ testCase "Nixpkgs parses without errors" ensureNixpkgsCanParse
112112
| isJust nixpkgsTestsEnv ]

tests/NixLanguageTests.hs

Lines changed: 23 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ From (git://nix)/tests/lang.sh we see that
6060
-}
6161

6262
groupBy :: Ord k => (v -> k) -> [v] -> Map k [v]
63-
groupBy key = Map.fromListWith (++) . fmap (key &&& pure)
63+
groupBy key = Map.fromListWith (<>) . fmap (key &&& pure)
6464

6565
-- | New tests, which have never yet passed. Once any of these is passing,
6666
-- please remove it from this list. Do not add tests to this list if they have
@@ -101,13 +101,13 @@ genTests = do
101101
["parse", "fail"] -> assertParseFail opts $ the files
102102
["eval" , "okay"] -> assertEval opts files
103103
["eval" , "fail"] -> assertEvalFail $ the files
104-
_ -> error $ "Unexpected: " ++ show kind
104+
_ -> error $ "Unexpected: " <> show kind
105105

106106
assertParse :: Options -> FilePath -> Assertion
107107
assertParse _opts file = parseNixFileLoc file >>= \case
108108
Success _expr -> pure () -- pure $! runST $ void $ lint opts expr
109109
Failure err ->
110-
assertFailure $ "Failed to parse " ++ file ++ ":\n" ++ show err
110+
assertFailure $ "Failed to parse " <> file <> ":\n" <> show err
111111

112112
assertParseFail :: Options -> FilePath -> Assertion
113113
assertParseFail opts file = do
@@ -118,40 +118,40 @@ assertParseFail opts file = do
118118
_ <- pure $! runST $ void $ lint opts expr
119119
assertFailure
120120
$ "Unexpected success parsing `"
121-
++ file
122-
++ ":\nParsed value: "
123-
++ show expr
121+
<> file
122+
<> ":\nParsed value: "
123+
<> show expr
124124
Failure _ -> pure ()
125125
)
126126
$ \(_ :: SomeException) -> pure ()
127127

128128
assertLangOk :: Options -> FilePath -> Assertion
129129
assertLangOk opts file = do
130-
actual <- printNix <$> hnixEvalFile opts (file ++ ".nix")
131-
expected <- Text.readFile $ file ++ ".exp"
132-
assertEqual "" expected $ Text.pack (actual ++ "\n")
130+
actual <- printNix <$> hnixEvalFile opts (file <> ".nix")
131+
expected <- Text.readFile $ file <> ".exp"
132+
assertEqual "" expected $ Text.pack (actual <> "\n")
133133

134134
assertLangOkXml :: Options -> FilePath -> Assertion
135135
assertLangOkXml opts file = do
136136
actual <- stringIgnoreContext . toXML <$> hnixEvalFile
137137
opts
138-
(file ++ ".nix")
139-
expected <- Text.readFile $ file ++ ".exp.xml"
138+
(file <> ".nix")
139+
expected <- Text.readFile $ file <> ".exp.xml"
140140
assertEqual "" expected actual
141141

142142
assertEval :: Options -> [FilePath] -> Assertion
143143
assertEval _opts files = do
144144
time <- liftIO getCurrentTime
145145
let opts = defaultOptions time
146146
case delete ".nix" $ sort $ fmap takeExtensions files of
147-
[] -> () <$ hnixEvalFile opts (name ++ ".nix")
147+
[] -> () <$ hnixEvalFile opts (name <> ".nix")
148148
[".exp" ] -> assertLangOk opts name
149149
[".exp.xml" ] -> assertLangOkXml opts name
150150
[".exp.disabled"] -> pure ()
151151
[".exp-disabled"] -> pure ()
152152
[".exp", ".flags"] -> do
153153
liftIO $ setEnv "NIX_PATH" "lang/dir4:lang/dir5"
154-
flags <- Text.readFile (name ++ ".flags")
154+
flags <- Text.readFile (name <> ".flags")
155155
let flags' | Text.last flags == '\n' = Text.init flags
156156
| otherwise = flags
157157
case
@@ -163,18 +163,18 @@ assertEval _opts files = do
163163
Opts.Failure err ->
164164
errorWithoutStackTrace
165165
$ "Error parsing flags from "
166-
++ name
167-
++ ".flags: "
168-
++ show err
166+
<> name
167+
<> ".flags: "
168+
<> show err
169169
Opts.Success opts' -> assertLangOk opts' name
170170
Opts.CompletionInvoked _ -> error "unused"
171-
_ -> assertFailure $ "Unknown test type " ++ show files
171+
_ -> assertFailure $ "Unknown test type " <> show files
172172
where
173173
name =
174-
"data/nix/tests/lang/" ++ the (fmap (takeFileName . dropExtensions) files)
174+
"data/nix/tests/lang/" <> the (fmap (takeFileName . dropExtensions) files)
175175

176-
fixup ("--arg" : x : y : rest) = "--arg" : (x ++ "=" ++ y) : fixup rest
177-
fixup ("--argstr" : x : y : rest) = "--argstr" : (x ++ "=" ++ y) : fixup rest
176+
fixup ("--arg" : x : y : rest) = "--arg" : (x <> "=" <> y) : fixup rest
177+
fixup ("--argstr" : x : y : rest) = "--argstr" : (x <> "=" <> y) : fixup rest
178178
fixup (x : rest) = x : fixup rest
179179
fixup [] = []
180180

@@ -185,6 +185,6 @@ assertEvalFail file = catch ?? (\(_ :: SomeException) -> pure ()) $ do
185185
evalResult
186186
`seq` assertFailure
187187
$ file
188-
++ " should not evaluate.\nThe evaluation result was `"
189-
++ evalResult
190-
++ "`."
188+
<> " should not evaluate.\nThe evaluation result was `"
189+
<> evalResult
190+
<> "`."

tests/ParserTests.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -367,27 +367,27 @@ tests = $testGroupGenerator
367367
assertParseText :: Text -> NExpr -> Assertion
368368
assertParseText str expected = case parseNixText str of
369369
Success actual ->
370-
assertEqual ("When parsing " ++ unpack str)
370+
assertEqual ("When parsing " <> unpack str)
371371
(stripPositionInfo expected) (stripPositionInfo actual)
372372
Failure err ->
373-
assertFailure $ "Unexpected error parsing `" ++ unpack str ++ "':\n" ++ show err
373+
assertFailure $ "Unexpected error parsing `" <> unpack str <> "':\n" <> show err
374374

375375
assertParseFile :: FilePath -> NExpr -> Assertion
376376
assertParseFile file expected = do
377-
res <- parseNixFile $ "data/" ++ file
377+
res <- parseNixFile $ "data/" <> file
378378
case res of
379-
Success actual -> assertEqual ("Parsing data file " ++ file)
379+
Success actual -> assertEqual ("Parsing data file " <> file)
380380
(stripPositionInfo expected) (stripPositionInfo actual)
381381
Failure err ->
382382
assertFailure $ "Unexpected error parsing data file `"
383-
++ file ++ "':\n" ++ show err
383+
<> file <> "':\n" <> show err
384384

385385
assertParseFail :: Text -> Assertion
386386
assertParseFail str = case parseNixText str of
387387
Failure _ -> pure ()
388388
Success r ->
389389
assertFailure $ "Unexpected success parsing `"
390-
++ unpack str ++ ":\nParsed value: " ++ show r
390+
<> unpack str <> ":\nParsed value: " <> show r
391391

392392
-- assertRoundTrip :: Text -> Assertion
393393
-- assertRoundTrip src = assertParsePrint src src

tests/PrettyParseTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,7 @@ genExpr = Gen.sized $ \(Size n) -> Fix <$> if n < 2
118118
genList = NList <$> fairList genExpr
119119
genSet = NSet NNonRecursive <$> fairList genBinding
120120
genRecSet = NSet NRecursive <$> fairList genBinding
121-
genLiteralPath = NLiteralPath . ("./" ++) <$> asciiString
121+
genLiteralPath = NLiteralPath . ("./" <>) <$> asciiString
122122
genEnvPath = NEnvPath <$> asciiString
123123
genUnary = NUnary <$> Gen.enumBounded <*> genExpr
124124
genBinary = NBinary <$> Gen.enumBounded <*> genExpr <*> genExpr

tests/PrettyTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,4 +35,4 @@ tests = $testGroupGenerator
3535
---------------------------------------------------------------------------------
3636
assertPretty :: NExpr -> String -> Assertion
3737
assertPretty e s =
38-
assertEqual ("When pretty-printing " ++ show e) s . show $ prettyNix e
38+
assertEqual ("When pretty-printing " <> show e) s . show $ prettyNix e

tests/TestCommon.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ hnixEvalFile opts file = do
2727
parseResult <- parseNixFileLoc file
2828
case parseResult of
2929
Failure err ->
30-
error $ "Parsing failed for file `" ++ file ++ "`.\n" ++ show err
30+
error $ "Parsing failed for file `" <> file <> "`.\n" <> show err
3131
Success expr -> do
3232
setEnv "TEST_VAR" "foo"
3333
runWithBasicEffects opts
@@ -45,9 +45,9 @@ hnixEvalText opts src = case parseNixText src of
4545
Failure err ->
4646
error
4747
$ "Parsing failed for expression `"
48-
++ unpack src
49-
++ "`.\n"
50-
++ show err
48+
<> unpack src
49+
<> "`.\n"
50+
<> show err
5151
Success expr ->
5252
runWithBasicEffects opts $ normalForm =<< nixEvalExpr Nothing expr
5353

@@ -66,14 +66,14 @@ nixEvalFile fp = readProcess "nix-instantiate" ["--eval", "--strict", fp] ""
6666
assertEvalFileMatchesNix :: FilePath -> Assertion
6767
assertEvalFileMatchesNix fp = do
6868
time <- liftIO getCurrentTime
69-
hnixVal <- (++ "\n") . printNix <$> hnixEvalFile (defaultOptions time) fp
69+
hnixVal <- (<> "\n") . printNix <$> hnixEvalFile (defaultOptions time) fp
7070
nixVal <- nixEvalFile fp
7171
assertEqual fp nixVal hnixVal
7272

7373
assertEvalMatchesNix :: Text -> Assertion
7474
assertEvalMatchesNix expr = do
7575
time <- liftIO getCurrentTime
76-
hnixVal <- (++ "\n") . printNix <$> hnixEvalText (defaultOptions time) expr
76+
hnixVal <- (<> "\n") . printNix <$> hnixEvalText (defaultOptions time) expr
7777
nixVal <- nixEvalString expr'
7878
assertEqual expr' nixVal hnixVal
7979
where expr' = unpack expr

0 commit comments

Comments
 (0)