Skip to content

Commit 5933d46

Browse files
committed
treewide: switch to new demand all remained cases
Builtins, it is 44 uses. Other also. Some refactor in the process. Couple of monadic binds become functors. After this change the code allows more refactors - move `demand`s into `do` blocks and fold the `do` blocks.
1 parent 7712fc4 commit 5933d46

File tree

11 files changed

+434
-509
lines changed

11 files changed

+434
-509
lines changed

main/Main.hs

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -214,17 +214,18 @@ main = do
214214
_ -> (True, True)
215215

216216
forceEntry k v =
217-
catch (pure <$> demandF pure v) $ \(NixException frames) -> do
218-
liftIO
219-
. putStrLn
220-
. ("Exception forcing " <>)
221-
. (k <>)
222-
. (": " <>)
223-
. show
224-
=<< renderFrames @(StdValue (StandardT (StdIdT IO)))
225-
@(StdThunk (StandardT (StdIdT IO)))
226-
frames
227-
pure Nothing
217+
catch (pure <$> (pure =<< demand v)) $ \(NixException frames) ->
218+
do
219+
liftIO
220+
. putStrLn
221+
. ("Exception forcing " <>)
222+
. (k <>)
223+
. (": " <>)
224+
. show
225+
=<< renderFrames @(StdValue (StandardT (StdIdT IO)))
226+
@(StdThunk (StandardT (StdIdT IO)))
227+
frames
228+
pure Nothing
228229

229230
reduction path mp x = do
230231
eres <- Nix.withNixContext mp

main/Repl.hs

Lines changed: 48 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ import Nix hiding ( exec
2727
)
2828
import Nix.Scope
2929
import Nix.Utils
30-
import Nix.Value.Monad ( demandF )
30+
import Nix.Value.Monad ( demand )
3131

3232
import qualified Data.List
3333
import qualified Data.Maybe
@@ -340,69 +340,74 @@ completion = System.Console.Repline.Prefix
340340
-- | Main completion function
341341
--
342342
-- Heavily inspired by Dhall Repl, with `algebraicComplete`
343-
-- adjusted to monadic variant able to `demandF` thunks.
343+
-- adjusted to monadic variant able to `demand` thunks.
344344
completeFunc
345345
:: forall e t f m . (MonadNix e t f m, MonadIO m)
346346
=> String
347347
-> String
348348
-> (StateT (IState t f m) m) [Completion]
349349
completeFunc reversedPrev word
350350
-- Commands
351-
| reversedPrev == ":"
352-
= pure . listCompletion
351+
| reversedPrev == ":" =
352+
pure . listCompletion
353353
$ fmap helpOptionName (helpOptions :: HelpOptions e t f m)
354354

355355
-- Files
356-
| any (`Data.List.isPrefixOf` word) [ "/", "./", "../", "~/" ]
357-
= listFiles word
356+
| any (`Data.List.isPrefixOf` word) [ "/", "./", "../", "~/" ] =
357+
listFiles word
358358

359359
-- Attributes of sets in REPL context
360-
| var : subFields <- Data.Text.split (== '.') (Data.Text.pack word)
361-
, not $ null subFields
362-
= do
363-
s <- get
364-
case Data.HashMap.Lazy.lookup var (replCtx s) of
365-
Nothing -> pure mempty
366-
Just binding -> do
367-
candidates <- lift $ algebraicComplete subFields binding
368-
pure $ notFinished <$> listCompletion (Data.Text.unpack . (var <>) <$> candidates)
360+
| var : subFields <- Data.Text.split (== '.') (Data.Text.pack word) , not $ null subFields =
361+
do
362+
s <- get
363+
maybe
364+
(pure mempty)
365+
(\ binding ->
366+
do
367+
candidates <- lift $ algebraicComplete subFields binding
368+
pure $ notFinished <$> listCompletion (Data.Text.unpack . (var <>) <$> candidates)
369+
)
370+
(Data.HashMap.Lazy.lookup var (replCtx s))
369371

370372
-- Builtins, context variables
371-
| otherwise
372-
= do
373-
s <- get
374-
let contextKeys = Data.HashMap.Lazy.keys (replCtx s)
375-
(Just (NVSet builtins _)) = Data.HashMap.Lazy.lookup "builtins" (replCtx s)
376-
shortBuiltins = Data.HashMap.Lazy.keys builtins
377-
378-
pure $ listCompletion
379-
$ ["__includes"]
380-
<> (Data.Text.unpack <$> contextKeys)
381-
<> (Data.Text.unpack <$> shortBuiltins)
373+
| otherwise =
374+
do
375+
s <- get
376+
let contextKeys = Data.HashMap.Lazy.keys (replCtx s)
377+
(Just (NVSet builtins _)) = Data.HashMap.Lazy.lookup "builtins" (replCtx s)
378+
shortBuiltins = Data.HashMap.Lazy.keys builtins
379+
380+
pure $ listCompletion
381+
$ ["__includes"]
382+
<> (Data.Text.unpack <$> contextKeys)
383+
<> (Data.Text.unpack <$> shortBuiltins)
382384

383385
where
384386
listCompletion = fmap simpleCompletion . filter (word `Data.List.isPrefixOf`)
385387

386388
notFinished x = x { isFinished = False }
387389

388-
algebraicComplete :: (MonadNix e t f m)
389-
=> [Text]
390-
-> NValue t f m
391-
-> m [Text]
390+
algebraicComplete
391+
:: (MonadNix e t f m)
392+
=> [Text]
393+
-> NValue t f m
394+
-> m [Text]
392395
algebraicComplete subFields val =
393-
let keys = fmap ("." <>) . Data.HashMap.Lazy.keys
394-
withMap m =
395-
case subFields of
396-
[] -> pure $ keys m
397-
-- Stop on last subField (we care about the keys at this level)
398-
[_] -> pure $ keys m
399-
f:fs ->
400-
maybe
401-
(pure mempty)
402-
(demandF (\e' -> (fmap . fmap) (("." <> f) <>) $ algebraicComplete fs e'))
403-
(Data.HashMap.Lazy.lookup f m)
404-
405-
in case val of
396+
let
397+
keys = fmap ("." <>) . Data.HashMap.Lazy.keys
398+
399+
withMap m =
400+
case subFields of
401+
[] -> pure $ keys m
402+
-- Stop on last subField (we care about the keys at this level)
403+
[_] -> pure $ keys m
404+
f:fs ->
405+
maybe
406+
(pure mempty)
407+
(((fmap . fmap) (("." <> f) <>) . algebraicComplete fs) <=< demand)
408+
(Data.HashMap.Lazy.lookup f m)
409+
in
410+
case val of
406411
NVSet xs _ -> withMap xs
407412
_ -> pure mempty
408413

src/Nix.hs

Lines changed: 25 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -115,14 +115,12 @@ evaluateExpression mpath evaluator handler expr = do
115115
(second mkStr)
116116
(argstr opts)
117117
evaluator mpath expr >>= \f ->
118-
demandF
119-
(\f' ->
120-
processResult handler =<<
121-
case f' of
122-
NVClosure _ g -> g (argmap args)
123-
_ -> pure f
124-
)
125-
f
118+
(\f' ->
119+
processResult handler =<<
120+
case f' of
121+
NVClosure _ g -> g (argmap args)
122+
_ -> pure f
123+
) =<< demand f
126124
where
127125
parseArg s =
128126
case parseNixText s of
@@ -149,29 +147,25 @@ processResult h val = do
149147
go :: [Text.Text] -> NValue t f m -> m a
150148
go [] v = h v
151149
go ((Text.decimal -> Right (n,"")) : ks) v =
152-
demandF
153-
(\case
154-
NVList xs ->
155-
list
150+
(\case
151+
NVList xs ->
152+
list
153+
h
154+
go
155+
ks
156+
(xs !! n)
157+
_ -> errorWithoutStackTrace $ "Expected a list for selector '" <> show n <> "', but got: " <> show v
158+
) =<< demand v
159+
go (k : ks) v =
160+
(\case
161+
NVSet xs _ ->
162+
maybe
163+
(errorWithoutStackTrace $ "Set does not contain key '" <> Text.unpack k <> "'")
164+
(list
156165
h
157166
go
158167
ks
159-
(xs !! n)
160-
_ -> errorWithoutStackTrace $ "Expected a list for selector '" <> show n <> "', but got: " <> show v
161-
)
162-
v
163-
go (k : ks) v =
164-
demandF
165-
(\case
166-
NVSet xs _ ->
167-
maybe
168-
(errorWithoutStackTrace $ "Set does not contain key '" <> Text.unpack k <> "'")
169-
(list
170-
h
171-
go
172-
ks
173-
)
174-
(M.lookup k xs)
175-
_ -> errorWithoutStackTrace $ "Expected a set for selector '" <> Text.unpack k <> "', but got: " <> show v
176-
)
177-
v
168+
)
169+
(M.lookup k xs)
170+
_ -> errorWithoutStackTrace $ "Expected a set for selector '" <> Text.unpack k <> "', but got: " <> show v
171+
) =<< demand v

0 commit comments

Comments
 (0)