Skip to content

Commit 595bb0a

Browse files
committed
m clean-ups
1 parent 5a97223 commit 595bb0a

File tree

5 files changed

+12
-14
lines changed

5 files changed

+12
-14
lines changed

main/Repl.hs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -106,12 +106,12 @@ main' iniVal =
106106
(prefixedCommand : xs) | Text.head prefixedCommand == commandPrefix ->
107107
do
108108
let
109-
arguments = Text.unwords xs
109+
arguments = unwords xs
110110
command = Text.tail prefixedCommand
111111
optMatcher command options arguments
112-
x -> cmd $ Text.unwords x
112+
x -> cmd $ unwords x
113113
)
114-
(Text.words <$> lines f)
114+
(words <$> lines f)
115115

116116
handleMissing e
117117
| Error.isDoesNotExistError e = pure ""
@@ -332,12 +332,14 @@ quit _ = liftIO Exit.exitSuccess
332332
-- | @:set@ command
333333
setConfig :: (MonadNix e t f m, MonadIO m) => Text -> Repl e t f m ()
334334
setConfig args =
335-
case Text.words args of
336-
[] -> liftIO $ Text.putStrLn "No option to set specified"
337-
(x:_xs) ->
335+
list
336+
(liftIO $ Text.putStrLn "No option to set specified")
337+
(\ (x:_xs) ->
338338
case filter ((==x) . helpSetOptionName) helpSetOptions of
339339
[opt] -> modify (\s -> s { replCfg = helpSetOptionFunction opt (replCfg s) })
340340
_ -> liftIO $ Text.putStrLn "No such option"
341+
)
342+
$ words args
341343

342344

343345
-- * Interactive Shell

src/Nix/Builtins.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@
55
{-# LANGUAGE KindSignatures #-}
66
{-# LANGUAGE MonoLocalBinds #-}
77
{-# LANGUAGE MultiWayIf #-}
8-
{-# LANGUAGE PackageImports #-}
98
{-# LANGUAGE PartialTypeSignatures #-}
109
{-# LANGUAGE QuasiQuotes #-}
1110
{-# LANGUAGE ScopedTypeVariables #-}
@@ -49,7 +48,6 @@ import qualified Data.HashMap.Lazy as M
4948
import Data.Scientific
5049
import qualified Data.Set as S
5150
import qualified Data.Text as Text
52-
import qualified Data.Text.Lazy as LazyText
5351
import qualified Data.Text.Lazy.Builder as Builder
5452
import Data.These ( fromThese )
5553
import qualified Data.Time.Clock.POSIX as Time
@@ -1030,7 +1028,7 @@ replaceStringsNix tfrom tto ts =
10301028

10311029
-- 2021-02-18: NOTE: rly?: toStrict . toLazyText
10321030
-- Maybe `text-builder`, `text-show`?
1033-
finish ctx output = makeNixString (LazyText.toStrict $ Builder.toLazyText output) ctx
1031+
finish ctx output = makeNixString (toStrict $ Builder.toLazyText output) ctx
10341032

10351033
replace (key, replacementNS, unprocessedInput) = replaceWithNixBug unprocessedInput updatedOutput
10361034

src/Nix/Effects.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,6 @@ import Nix.Render
3333
import Nix.Value
3434
import qualified Paths_hnix
3535
import System.Exit
36-
import qualified System.Environment as Env
3736
import System.FilePath ( takeFileName )
3837
import qualified System.Info
3938
import System.Process
@@ -235,7 +234,7 @@ class
235234
-- ** Instances
236235

237236
instance MonadEnv IO where
238-
getEnvVar = (<<$>>) toText . Env.lookupEnv . toString
237+
getEnvVar = (<<$>>) toText . lookupEnv . toString
239238

240239
getCurrentSystemOS = pure $ toText System.Info.os
241240

tests/Main.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22

33
module Main where
44

5-
import Prelude hiding (lookupEnv)
65
import Relude.Unsafe (read)
76
import qualified Control.Exception as Exc
87
import GHC.Err (errorWithoutStackTrace)
@@ -25,7 +24,7 @@ import qualified PrettyTests
2524
import qualified ReduceExprTests
2625
import qualified PrettyParseTests
2726
import System.Directory
28-
import System.Environment (setEnv, lookupEnv)
27+
import System.Environment (setEnv)
2928
import System.FilePath.Glob
3029
import System.Posix.Files
3130
import Test.Tasty

tests/ParserTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -222,7 +222,7 @@ case_inherit_selector_syntax_mistakes =
222222

223223
case_int_list =
224224
checks
225-
( mkList $ mkInt <$> [ i | i <- [1,2,3] ]
225+
( mkList $ mkInt <$> [1,2,3]
226226
, "[1 2 3]"
227227
)
228228

0 commit comments

Comments
 (0)