Skip to content

Commit d699071

Browse files
committed
(Just -> pure)
1 parent 9c4b44e commit d699071

File tree

25 files changed

+130
-130
lines changed

25 files changed

+130
-130
lines changed

main/Main.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ main = do
5151
runWithBasicEffectsIO opts $ case readFrom opts of
5252
Just path -> do
5353
let file = addExtension (dropExtension path) "nixc"
54-
process opts (Just file) =<< liftIO (readCache path)
54+
process opts (pure file) =<< liftIO (readCache path)
5555
Nothing -> case expression opts of
5656
Just s -> handleResult opts Nothing (parseNixTextLoc s)
5757
Nothing -> case fromFile opts of
@@ -68,7 +68,7 @@ main = do
6868
where
6969
processFile opts path = do
7070
eres <- parseNixFileLoc path
71-
handleResult opts (Just path) eres
71+
handleResult opts (pure path) eres
7272

7373
handleResult opts mpath = \case
7474
Failure err ->
@@ -102,7 +102,7 @@ main = do
102102
if evaluate opts
103103
then do
104104
val <- Nix.nixEvalExprLoc mpath expr
105-
withNixContext Nothing (Repl.main' $ Just val)
105+
withNixContext Nothing (Repl.main' $ pure val)
106106
else withNixContext Nothing Repl.main
107107

108108
process opts mpath expr
@@ -165,7 +165,7 @@ main = do
165165
where
166166
go prefix s = do
167167
xs <- forM (sortOn fst (M.toList s)) $ \(k, nv) -> case nv of
168-
Free v -> pure (k, Just (Free v))
168+
Free v -> pure (k, pure (Free v))
169169
Pure (StdThunk (extract -> Thunk _ _ ref)) -> do
170170
let path = prefix <> Text.unpack k
171171
(_, descend) = filterEntry path k
@@ -204,7 +204,7 @@ main = do
204204
_ -> (True, True)
205205

206206
forceEntry k v =
207-
catch (Just <$> demand v pure) $ \(NixException frames) -> do
207+
catch (pure <$> demand v pure) $ \(NixException frames) -> do
208208
liftIO
209209
. putStrLn
210210
. ("Exception forcing " <>)

main/Repl.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -76,8 +76,8 @@ main' iniVal = initState iniVal >>= \s -> flip evalStateT s
7676
banner
7777
cmd
7878
options
79-
(Just commandPrefix)
80-
(Just "paste")
79+
(pure commandPrefix)
80+
(pure "paste")
8181
completion
8282
(rcFile >> greeter)
8383
finalizer
@@ -212,14 +212,14 @@ exec update source = do
212212
-- Update the interpreter state
213213
when (update && isBinding) $ do
214214
-- Set `replIt` to last entered expression
215-
put st { replIt = Just expr }
215+
put st { replIt = pure expr }
216216

217217
-- If the result value is a set, update our context with it
218218
case val of
219219
NVSet xs _ -> put st { replCtx = Data.HashMap.Lazy.union xs (replCtx st) }
220220
_ -> pure ()
221221

222-
pure $ Just val
222+
pure $ pure val
223223
where
224224
-- If parsing fails, turn the input into singleton attribute set
225225
-- and try again.
@@ -292,7 +292,7 @@ typeof
292292
typeof args = do
293293
st <- get
294294
mVal <- case Data.HashMap.Lazy.lookup line (replCtx st) of
295-
Just val -> pure $ Just val
295+
Just val -> pure $ pure val
296296
Nothing -> do
297297
exec False line
298298

@@ -329,7 +329,7 @@ completion
329329
:: (MonadNix e t f m, MonadIO m)
330330
=> CompleterStyle (StateT (IState t f m) m)
331331
completion = System.Console.Repline.Prefix
332-
(completeWordWithPrev (Just '\\') separators completeFunc)
332+
(completeWordWithPrev (pure '\\') separators completeFunc)
333333
defaultMatcher
334334
where
335335
separators :: String

src/Nix/Builtins.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -332,7 +332,7 @@ foldNixPath f z = do
332332
| otherwise = (x, PathEntryPath)
333333
go (x, ty) rest = case Text.splitOn "=" x of
334334
[p] -> f (Text.unpack p) Nothing ty rest
335-
[n, p] -> f (Text.unpack p) (Just (Text.unpack n)) ty rest
335+
[n, p] -> f (Text.unpack p) (pure (Text.unpack n)) ty rest
336336
_ -> throwError $ ErrorCall $ "Unexpected entry in NIX_PATH: " <> show x
337337

338338
nixPath :: MonadNix e t f m => m (NValue t f m)
@@ -825,7 +825,7 @@ elem_ x = toValue <=< anyM (valueEqM x) <=< fromValue
825825
elemAt :: [a] -> Int -> Maybe a
826826
elemAt ls i = case drop i ls of
827827
[] -> Nothing
828-
a : _ -> Just a
828+
a : _ -> pure a
829829

830830
elemAt_
831831
:: MonadNix e t f m
@@ -1108,7 +1108,7 @@ scopedImport asetArg pathArg = fromValue @(AttrSet (NValue t f m)) asetArg >>= \
11081108
traceM $ "Current file being evaluated is: " <> show p'
11091109
pure $ takeDirectory p' </> path
11101110
clearScopes @(NValue t f m)
1111-
$ withNixContext (Just path')
1111+
$ withNixContext (pure path')
11121112
$ pushScope s
11131113
$ importPath @t @f @m path'
11141114

src/Nix/Convert.hs

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -98,7 +98,7 @@ instance ( Convertible e t f m
9898
instance Convertible e t f m
9999
=> FromValue () m (NValue' t f m (NValue t f m)) where
100100
fromValueMay = \case
101-
NVConstant' NNull -> pure $ Just ()
101+
NVConstant' NNull -> pure $ pure ()
102102
_ -> pure Nothing
103103
fromValue v = fromValueMay v >>= \case
104104
Just b -> pure b
@@ -107,7 +107,7 @@ instance Convertible e t f m
107107
instance Convertible e t f m
108108
=> FromValue Bool m (NValue' t f m (NValue t f m)) where
109109
fromValueMay = \case
110-
NVConstant' (NBool b) -> pure $ Just b
110+
NVConstant' (NBool b) -> pure $ pure b
111111
_ -> pure Nothing
112112
fromValue v = fromValueMay v >>= \case
113113
Just b -> pure b
@@ -116,7 +116,7 @@ instance Convertible e t f m
116116
instance Convertible e t f m
117117
=> FromValue Int m (NValue' t f m (NValue t f m)) where
118118
fromValueMay = \case
119-
NVConstant' (NInt b) -> pure $ Just (fromInteger b)
119+
NVConstant' (NInt b) -> pure $ pure (fromInteger b)
120120
_ -> pure Nothing
121121
fromValue v = fromValueMay v >>= \case
122122
Just b -> pure b
@@ -125,7 +125,7 @@ instance Convertible e t f m
125125
instance Convertible e t f m
126126
=> FromValue Integer m (NValue' t f m (NValue t f m)) where
127127
fromValueMay = \case
128-
NVConstant' (NInt b) -> pure $ Just b
128+
NVConstant' (NInt b) -> pure $ pure b
129129
_ -> pure Nothing
130130
fromValue v = fromValueMay v >>= \case
131131
Just b -> pure b
@@ -134,8 +134,8 @@ instance Convertible e t f m
134134
instance Convertible e t f m
135135
=> FromValue Float m (NValue' t f m (NValue t f m)) where
136136
fromValueMay = \case
137-
NVConstant' (NFloat b) -> pure $ Just b
138-
NVConstant' (NInt i) -> pure $ Just (fromInteger i)
137+
NVConstant' (NFloat b) -> pure $ pure b
138+
NVConstant' (NInt i) -> pure $ pure (fromInteger i)
139139
_ -> pure Nothing
140140
fromValue v = fromValueMay v >>= \case
141141
Just b -> pure b
@@ -147,9 +147,9 @@ instance ( Convertible e t f m
147147
)
148148
=> FromValue NixString m (NValue' t f m (NValue t f m)) where
149149
fromValueMay = \case
150-
NVStr' ns -> pure $ Just ns
150+
NVStr' ns -> pure $ pure ns
151151
NVPath' p ->
152-
Just
152+
pure
153153
. (\s -> makeNixStringWithSingletonContext s (StringContext s DirectPath))
154154
. Text.pack
155155
. unStorePath
@@ -179,7 +179,7 @@ instance ( Convertible e t f m
179179
)
180180
=> FromValue Path m (NValue' t f m (NValue t f m)) where
181181
fromValueMay = \case
182-
NVPath' p -> pure $ Just (Path p)
182+
NVPath' p -> pure $ pure (Path p)
183183
NVStr' ns -> pure $ Path . Text.unpack <$> getStringNoContext ns
184184
NVSet' s _ -> case M.lookup "outPath" s of
185185
Nothing -> pure Nothing
@@ -192,7 +192,7 @@ instance ( Convertible e t f m
192192
instance Convertible e t f m
193193
=> FromValue [NValue t f m] m (NValue' t f m (NValue t f m)) where
194194
fromValueMay = \case
195-
NVList' l -> pure $ Just l
195+
NVList' l -> pure $ pure l
196196
_ -> pure Nothing
197197
fromValue v = fromValueMay v >>= \case
198198
Just b -> pure b
@@ -212,7 +212,7 @@ instance ( Convertible e t f m
212212
instance Convertible e t f m
213213
=> FromValue (AttrSet (NValue t f m)) m (NValue' t f m (NValue t f m)) where
214214
fromValueMay = \case
215-
NVSet' s _ -> pure $ Just s
215+
NVSet' s _ -> pure $ pure s
216216
_ -> pure Nothing
217217
fromValue v = fromValueMay v >>= \case
218218
Just b -> pure b
@@ -233,7 +233,7 @@ instance Convertible e t f m
233233
=> FromValue (AttrSet (NValue t f m), AttrSet SourcePos) m
234234
(NValue' t f m (NValue t f m)) where
235235
fromValueMay = \case
236-
NVSet' s p -> pure $ Just (s, p)
236+
NVSet' s p -> pure $ pure (s, p)
237237
_ -> pure Nothing
238238
fromValue v = fromValueMay v >>= \case
239239
Just b -> pure b
@@ -352,17 +352,17 @@ instance (Convertible e t f m, ToValue a m (NValue t f m))
352352
instance Convertible e t f m
353353
=> ToValue NixLikeContextValue m (NValue' t f m (NValue t f m)) where
354354
toValue nlcv = do
355-
path <- if nlcvPath nlcv then Just <$> toValue True else pure Nothing
355+
path <- if nlcvPath nlcv then pure <$> toValue True else pure Nothing
356356
allOutputs <- if nlcvAllOutputs nlcv
357-
then Just <$> toValue True
357+
then pure <$> toValue True
358358
else pure Nothing
359359
outputs <- do
360360
let outputs =
361361
makeNixStringWithoutContext <$> nlcvOutputs nlcv
362362
ts :: [NValue t f m] <- traverse toValue outputs
363363
case ts of
364364
[] -> pure Nothing
365-
_ -> Just <$> toValue ts
365+
_ -> pure <$> toValue ts
366366
pure $ flip nvSet' M.empty $ M.fromList $ catMaybes
367367
[ ("path",) <$> path
368368
, ("allOutputs",) <$> allOutputs

src/Nix/Effects/Basic.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,7 @@ findEnvPathM name = do
107107
then makeAbsolutePath @t @f $ absPath </> "default.nix"
108108
else return absPath
109109
exists <- doesFileExist absFile
110-
pure $ if exists then Just absFile else Nothing
110+
pure $ if exists then pure absFile else Nothing
111111

112112
findPathBy
113113
:: forall e t f m
@@ -139,7 +139,7 @@ findPathBy finder ls name = do
139139
Just (nsPfx :: NixString) ->
140140
let pfx = stringIgnoreContext nsPfx
141141
in if not (Text.null pfx)
142-
then tryPath path (Just (Text.unpack pfx))
142+
then tryPath path (pure (Text.unpack pfx))
143143
else tryPath path Nothing
144144
_ -> tryPath path Nothing
145145

@@ -222,7 +222,7 @@ findPathM = findPathBy existingPath
222222
existingPath path = do
223223
apath <- makeAbsolutePath @t @f path
224224
exists <- doesPathExist apath
225-
pure $ if exists then Just apath else Nothing
225+
pure $ if exists then pure apath else Nothing
226226

227227
defaultImportPath
228228
:: (MonadNix e t f m, MonadState (HashMap FilePath NExprLoc, b) m)

src/Nix/Effects/Derivation.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -221,7 +221,7 @@ derivationParser = do
221221
[ht] -> (ht, Flat)
222222
_ -> error $ "Unsupported hash type for output of fixed-output derivation in .drv file: " <> show fullOutputs
223223
in case Store.mkNamedDigest hashType hash of
224-
Right digest -> (Just digest, hashMode)
224+
Right digest -> (pure digest, hashMode)
225225
Left err -> error $ "Unsupported hash " <> show (hashType <> ":" <> hash) <> "in .drv file: " <> err
226226
_ -> (Nothing, Flat)
227227

@@ -300,7 +300,7 @@ buildDerivationWithContext drvAttrs = do
300300
args <- getAttrOr "args" [] $ mapM (fromValue' >=> extractNixString)
301301
builder <- getAttr "builder" $ extractNixString
302302
platform <- getAttr "system" $ extractNoCtx >=> assertNonNull
303-
mHash <- getAttrOr "outputHash" Nothing $ extractNoCtx >=> (return . Just)
303+
mHash <- getAttrOr "outputHash" Nothing $ extractNoCtx >=> (return . pure)
304304
hashMode <- getAttrOr "outputHashMode" Flat $ extractNoCtx >=> parseHashMode
305305
outputs <- getAttrOr "outputs" ["out"] $ mapM (fromValue' >=> extractNoCtx)
306306

@@ -310,14 +310,14 @@ buildDerivationWithContext drvAttrs = do
310310
when (outputs /= ["out"]) $ lift $ throwError $ ErrorCall $ "Multiple outputs are not supported for fixed-output derivations"
311311
hashType <- getAttr "outputHashAlgo" $ extractNoCtx
312312
digest <- lift $ either (throwError . ErrorCall) return $ Store.mkNamedDigest hashType hash
313-
return $ Just digest
313+
return $ pure digest
314314

315315
-- filter out null values if needed.
316316
attrs <- if not ignoreNulls
317317
then return drvAttrs
318318
else M.mapMaybe id <$> forM drvAttrs (demand' ?? (\case
319319
NVConstant NNull -> return Nothing
320-
value -> return $ Just value
320+
value -> return $ pure value
321321
))
322322

323323
env <- if useJson

src/Nix/Eval.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -132,7 +132,7 @@ eval (NBinary NApp fun arg) = do
132132
eval (NBinary op larg rarg) = larg >>= evalBinary op ?? rarg
133133

134134
eval (NSelect aset attr alt ) = evalSelect aset attr >>= either go id
135-
where go (s, ks) = fromMaybe (attrMissing ks (Just s)) alt
135+
where go (s, ks) = fromMaybe (attrMissing ks (pure s)) alt
136136

137137
eval (NHasAttr aset attr) = evalSelect aset attr >>= toValue . isRight
138138

@@ -352,7 +352,7 @@ evalSetterKeyName
352352
=> NKeyName (m v)
353353
-> m (Maybe Text)
354354
evalSetterKeyName = \case
355-
StaticKey k -> pure (Just k)
355+
StaticKey k -> pure (pure k)
356356
DynamicKey k ->
357357
runAntiquoted "\n" assembleString (>>= fromValueMay) k <&> \case
358358
Just ns -> Just (stringIgnoreContext ns)
@@ -370,7 +370,7 @@ assembleString = \case
370370
fromParts = fmap (fmap mconcat . sequence) . traverse go
371371

372372
go = runAntiquoted "\n"
373-
(pure . Just . makeNixStringWithoutContext)
373+
(pure . pure . makeNixStringWithoutContext)
374374
(>>= fromValueMay)
375375

376376
buildArgument
@@ -398,25 +398,25 @@ buildArgument params arg = do
398398
-> Maybe (AttrSet v -> m v)
399399
assemble scope isVariadic k = \case
400400
That Nothing ->
401-
Just
401+
pure
402402
$ const
403403
$ evalError @v
404404
$ ErrorCall
405405
$ "Missing value for parameter: "
406406
<> show k
407407
That (Just f) ->
408-
Just $ \args -> defer $ withScopes scope $ pushScope args f
408+
pure $ \args -> defer $ withScopes scope $ pushScope args f
409409
This _
410410
| isVariadic
411411
-> Nothing
412412
| otherwise
413-
-> Just
413+
-> pure
414414
$ const
415415
$ evalError @v
416416
$ ErrorCall
417417
$ "Unexpected parameter: "
418418
<> show k
419-
These x _ -> Just (const (pure x))
419+
These x _ -> pure (const (pure x))
420420

421421
addSourcePositions
422422
:: (MonadReader e m, Has e SrcSpan) => Transform NExprLocF (m a)

0 commit comments

Comments
 (0)