Skip to content

Commit b2b4976

Browse files
committed
treewide: hlint clean-up
1 parent 77d148b commit b2b4976

File tree

25 files changed

+72
-72
lines changed

25 files changed

+72
-72
lines changed

main/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,7 @@ main' opts@Options{..} = runWithBasicEffectsIO opts execContentsFilesOrRepl
8686
(\binaryCacheFile ->
8787
do
8888
let file = replaceExtension binaryCacheFile "nixc"
89-
processCLIOptions (Just $ coerce file) =<< liftIO (readCache $ coerce $ binaryCacheFile)
89+
processCLIOptions (Just $ coerce file) =<< liftIO (readCache $ coerce binaryCacheFile)
9090
) <$> readFrom
9191

9292
-- | The `--expr` option: read expression from the argument string

main/Repl.hs

Lines changed: 5 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -15,9 +15,8 @@ module Repl
1515
, main'
1616
) where
1717

18-
import Nix hiding ( exec
19-
, try
20-
)
18+
import Prelude hiding ( state )
19+
import Nix hiding ( exec )
2120
import Nix.Scope
2221
import Nix.Utils
2322
import Nix.Value.Monad ( demand )
@@ -55,7 +54,6 @@ import System.Console.Repline ( Cmd
5554
import qualified System.Console.Repline as Console
5655
import qualified System.Exit as Exit
5756
import qualified System.IO.Error as Error
58-
import Prelude hiding (state)
5957

6058
-- | Repl entry point
6159
main :: (MonadNix e t f m, MonadIO m, MonadMask m) => m ()
@@ -116,7 +114,7 @@ main' iniVal =
116114

117115
handleMissing e
118116
| Error.isDoesNotExistError e = pure ""
119-
| otherwise = throwIO e
117+
| otherwise = throwM e
120118

121119
-- Replicated and slightly adjusted `optMatcher` from `System.Console.Repline`
122120
-- which doesn't export it.
@@ -136,9 +134,9 @@ main' iniVal =
136134
-- * Types
137135

138136
data IState t f m = IState
139-
{ replIt :: Maybe NExprLoc -- ^ Last expression entered
137+
{ replIt :: Maybe NExprLoc -- ^ Last expression entered
140138
, replCtx :: Scope (NValue t f m) -- ^ Scope. Value environment.
141-
, replCfg :: ReplConfig -- ^ REPL configuration
139+
, replCfg :: ReplConfig -- ^ REPL configuration
142140
} deriving (Eq, Show)
143141

144142
data ReplConfig = ReplConfig

src/Nix/Builtins.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ where
2323

2424

2525
import Prelude hiding ( traceM )
26+
import GHC.Exception ( ErrorCall(ErrorCall) )
2627
import Nix.Utils
2728
import Control.Comonad ( Comonad )
2829
import Control.Monad ( foldM )
@@ -1262,7 +1263,7 @@ scopedImportNix asetArg pathArg =
12621263
p' <- fromValue @Path =<< demand res
12631264

12641265
traceM $ "Current file being evaluated is: " <> show p'
1265-
pure $ coerce $ takeDirectory (coerce p') </> (coerce path)
1266+
pure $ coerce $ takeDirectory (coerce p') </> coerce path
12661267
)
12671268
=<< lookupVar "__cur_file"
12681269

@@ -1273,7 +1274,7 @@ scopedImportNix asetArg pathArg =
12731274

12741275
getEnvNix :: MonadNix e t f m => NValue t f m -> m (NValue t f m)
12751276
getEnvNix v =
1276-
(toValue . mkNixStringWithoutContext . fromMaybe mempty) =<< getEnvVar =<< fromStringNoContext =<< fromValue v
1277+
(toValue . mkNixStringWithoutContext . maybeToMonoid) =<< getEnvVar =<< fromStringNoContext =<< fromValue v
12771278

12781279
sortNix
12791280
:: MonadNix e t f m
@@ -1464,7 +1465,7 @@ readDirNix nvpath =
14641465
detectFileTypes :: Path -> m (VarName, FileType)
14651466
detectFileTypes item =
14661467
do
1467-
s <- getSymbolicLinkStatus $ coerce $ (coerce path) </> (coerce item)
1468+
s <- getSymbolicLinkStatus $ coerce $ on (</>) coerce path item
14681469
let
14691470
t =
14701471
if

src/Nix/Cache.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
-- | Reading and writing Nix cache files
44
module Nix.Cache where
55

6-
import qualified Data.ByteString.Lazy as BS
6+
import qualified Data.ByteString.Lazy as BSL
77
import Nix.Utils
88
import Nix.Expr.Types.Annotated
99

@@ -27,7 +27,7 @@ readCache path = do
2727
(\ expr -> pure $ C.getCompact expr)
2828
eres
2929
#else
30-
eres <- S.deserialiseOrFail <$> BS.readFile (coerce path)
30+
eres <- S.deserialiseOrFail <$> BSL.readFile (coerce path)
3131
either
3232
(\ err -> fail $ "Error reading cache file: " <> show err)
3333
pure
@@ -39,5 +39,5 @@ writeCache path expr =
3939
#ifdef USE_COMPACT
4040
C.writeCompact path =<< C.compact expr
4141
#else
42-
BS.writeFile (coerce path) (S.serialise expr)
42+
BSL.writeFile (coerce path) (S.serialise expr)
4343
#endif

src/Nix/Effects.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ import Prelude hiding ( traceM
1818
, print
1919
)
2020
import qualified Prelude
21+
import GHC.Exception ( ErrorCall(ErrorCall) )
2122
import Nix.Utils
2223
import qualified Data.HashSet as HS
2324
import qualified Data.Text as Text

src/Nix/Effects/Basic.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ import Prelude hiding ( traceM
77
, head
88
)
99
import Relude.Unsafe ( head )
10+
import GHC.Exception ( ErrorCall(ErrorCall) )
1011
import Nix.Utils
1112
import Control.Monad ( foldM )
1213
import qualified Data.HashMap.Lazy as M
@@ -58,7 +59,7 @@ defaultToAbsolutePath origPath = do
5859
removeDotDotIndirections <$> canonicalizePath absPath
5960

6061
expandHomePath :: MonadFile m => Path -> m Path
61-
expandHomePath (coerce -> ('~' : xs)) = (<> (coerce xs)) <$> getHomeDirectory
62+
expandHomePath (coerce -> ('~' : xs)) = (<> coerce xs) <$> getHomeDirectory
6263
expandHomePath p = pure p
6364

6465
-- | Incorrectly normalize paths by rewriting patterns like @a/b/..@ to @a@.
@@ -107,7 +108,7 @@ findEnvPathM name = do
107108
absFile <-
108109
bool
109110
(pure absPath)
110-
(toAbsolutePath @t @f $ coerce $ (coerce absPath) </> "default.nix")
111+
(toAbsolutePath @t @f $ coerce $ coerce absPath </> "default.nix")
111112
isDir
112113
exists <- doesFileExist absFile
113114
pure $
@@ -126,7 +127,7 @@ findPathBy
126127
findPathBy finder ls name = do
127128
mpath <- foldM go mempty ls
128129
maybe
129-
(throwError $ ErrorCall $ "file ''" <> (coerce name) <> "'' was not found in the Nix search path (add it's using $NIX_PATH or -I)")
130+
(throwError $ ErrorCall $ "file ''" <> coerce name <> "'' was not found in the Nix search path (add it's using $NIX_PATH or -I)")
130131
pure
131132
mpath
132133
where
@@ -161,8 +162,8 @@ findPathBy finder ls name = do
161162
mp
162163

163164
tryPath :: Path -> Maybe Path -> m (Maybe Path)
164-
tryPath p (Just n) | n' : ns <- splitDirectories (coerce name), n == (coerce n') =
165-
finder $ p <///> (coerce $ joinPath ns)
165+
tryPath p (Just n) | n' : ns <- splitDirectories (coerce name), n == coerce n' =
166+
finder $ p <///> coerce (joinPath ns)
166167
tryPath p _ = finder $ p <///> name
167168

168169
resolvePath s =

src/Nix/Effects/Derivation.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,8 @@
66

77
module Nix.Effects.Derivation ( defaultDerivationStrict ) where
88

9+
import Prelude hiding ( readFile )
10+
import GHC.Exception ( ErrorCall(ErrorCall) )
911
import Nix.Utils
1012
import Data.Char ( isAscii
1113
, isAlphaNum
@@ -41,7 +43,6 @@ import Nix.Value.Monad
4143
import qualified System.Nix.ReadonlyStore as Store
4244
import qualified System.Nix.Hash as Store
4345
import qualified System.Nix.StorePath as Store
44-
import Prelude hiding (readFile)
4546

4647

4748
-- 2021-07-17: NOTE: Derivation consists of @"keys"@ @"vals"@ (of text), so underlining type boundary currently stops here.

src/Nix/Eval.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ module Nix.Eval where
99

1010
import Control.Monad ( foldM )
1111
import Control.Monad.Fix ( MonadFix )
12+
import GHC.Exception ( ErrorCall(ErrorCall) )
1213
import Data.Semialign.Indexed ( ialignWith )
1314
import qualified Data.HashMap.Lazy as M
1415
import Data.List ( partition )
@@ -422,7 +423,7 @@ evalSelect aset attr =
422423
(pure $ Left (x, path))
423424
(list
424425
(pure . pure)
425-
(\ (y : ys) -> ((extract (y :| ys)) =<<))
426+
(\ (y : ys) -> (extract (y :| ys) =<<))
426427
ks
427428
. demand
428429
)
@@ -477,28 +478,27 @@ buildArgument
477478
buildArgument params arg =
478479
do
479480
scope <- currentScopes :: m (Scopes m v)
480-
let argThunk = defer $ withScopes scope arg
481+
let
482+
argThunk = defer $ withScopes scope arg
481483
case params of
482-
Param name -> M.singleton name <$> argThunk
484+
Param name -> one . (name,) <$> argThunk
483485
ParamSet mname variadic pset ->
484486
do
485487
(args, _) <- fromValue @(AttrSet v, PositionSet) =<< arg
486488
let
487489
inject =
488490
maybe
489491
id
490-
(\ n -> M.insert n $ const argThunk) -- why insert into const?
492+
(\ n -> M.insert n $ const argThunk) -- why insert into const? Thunk value getting magic point?
491493
mname
492-
loebM
493-
(inject $
494-
M.mapMaybe
495-
id
496-
(ialignWith
494+
loebM $
495+
inject $
496+
M.mapMaybe
497+
id
498+
$ ialignWith
497499
(assemble scope variadic)
498500
args
499501
$ M.fromList pset
500-
)
501-
)
502502
where
503503
assemble
504504
:: Scopes m v

src/Nix/Exec.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ import Prelude hiding ( putStr
1717
, putStrLn
1818
, print
1919
)
20-
20+
import GHC.Exception ( ErrorCall(ErrorCall) )
2121
import Control.Monad.Catch hiding ( catchJust )
2222
import Control.Monad.Fix
2323
import Data.Fix
@@ -422,7 +422,7 @@ 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-
toAbsolutePath @t @f (ls <> (coerce $ toString rs2))
425+
toAbsolutePath @t @f (ls <> coerce (toString rs2))
426426
)
427427
(getStringNoContext rs)
428428
(NVPath ls, NVPath rs) -> nvPathP prov <$> toAbsolutePath @t @f (ls <> rs)

src/Nix/Expr/Types.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -148,7 +148,7 @@ data Variadic = Closed | Variadic
148148
, Show, Read, Hashable
149149
)
150150

151-
instance Semigroup (Variadic) where
151+
instance Semigroup Variadic where
152152
(<>) Closed Closed = Closed
153153
(<>) _ _ = Variadic
154154

0 commit comments

Comments
 (0)