99
1010{-# LANGUAGE MultiWayIf #-}
1111{-# LANGUAGE ScopedTypeVariables #-}
12+ {-# LANGUAGE ViewPatterns #-}
1213
1314module Repl
1415 ( main
@@ -22,7 +23,7 @@ import Nix.Scope
2223import Nix.Utils
2324import Nix.Value.Monad ( demand )
2425
25- import qualified Data.HashMap.Lazy
26+ import qualified Data.HashMap.Lazy as M
2627import Data.Char ( isSpace )
2728import Data.List ( dropWhileEnd )
2829import qualified Data.Text as Text
@@ -55,6 +56,7 @@ import System.Console.Repline ( Cmd
5556import qualified System.Console.Repline as Console
5657import qualified System.Exit as Exit
5758import qualified System.IO.Error as Error
59+ import Prelude hiding (state )
5860
5961-- | Repl entry point
6062main :: (MonadNix e t f m , MonadIO m , MonadMask m ) => m ()
@@ -136,7 +138,7 @@ main' iniVal =
136138
137139data IState t f m = IState
138140 { replIt :: Maybe NExprLoc -- ^ Last expression entered
139- , replCtx :: AttrSet (NValue t f m ) -- ^ Value environment
141+ , replCtx :: Scope (NValue t f m ) -- ^ Scope. Value environment.
140142 , replCfg :: ReplConfig -- ^ REPL configuration
141143 } deriving (Eq , Show )
142144
@@ -159,14 +161,17 @@ initState mIni = do
159161
160162 builtins <- evalText " builtins"
161163
162- opts :: Nix. Options <- asks (view hasLens)
164+ let
165+ scope = coerce $
166+ M. fromList $
167+ (" builtins" , builtins) : fmap (" input" ,) (maybeToList mIni)
168+
169+ opts :: Nix. Options <- asks $ view hasLens
163170
164171 pure $
165172 IState
166173 Nothing
167- (Data.HashMap.Lazy. fromList $
168- (" builtins" , builtins) : fmap (" input" ,) (maybeToList mIni)
169- )
174+ scope
170175 defReplConfig
171176 { cfgStrict = strict opts
172177 , cfgValues = values opts
192197 -> Repl e t f m (Maybe (NValue t f m ))
193198exec update source = do
194199 -- Get the current interpreter state
195- st <- get
200+ state <- get
196201
197- when (cfgDebug $ replCfg st ) $ liftIO $ print st
202+ when (cfgDebug $ replCfg state ) $ liftIO $ print state
198203
199204 -- Parser ( returns AST as `NExprLoc` )
200205 case parseExprOrBinding source of
@@ -211,7 +216,7 @@ exec update source = do
211216 -- let tyctx' = inferTop mempty [("repl", stripAnnotation expr)]
212217 -- liftIO $ print tyctx'
213218
214- mVal <- lift $ lift $ try $ pushScope (replCtx st ) (evalExprLoc expr)
219+ mVal <- lift $ lift $ try $ pushScope (replCtx state ) (evalExprLoc expr)
215220
216221 either
217222 (\ (NixException frames) -> do
@@ -221,11 +226,11 @@ exec update source = do
221226 -- Update the interpreter state
222227 when (update && isBinding) $ do
223228 -- Set `replIt` to last entered expression
224- put st { replIt = pure expr }
229+ put state { replIt = pure expr }
225230
226231 -- If the result value is a set, update our context with it
227232 case val of
228- NVSet _ xs -> put st { replCtx = xs <> replCtx st }
233+ NVSet _ (coerce -> scope) -> put state { replCtx = scope <> replCtx state }
229234 _ -> pass
230235
231236 pure $ pure val
@@ -283,14 +288,14 @@ browse :: (MonadNix e t f m, MonadIO m)
283288 -> Repl e t f m ()
284289browse _ =
285290 do
286- st <- get
291+ state <- get
287292 traverse_
288293 (\ (k, v) ->
289294 do
290295 liftIO $ Text. putStr $ coerce k <> " = "
291296 printValue v
292297 )
293- (Data.HashMap.Lazy. toList $ replCtx st )
298+ (M. toList $ coerce $ replCtx state )
294299
295300-- | @:load@ command
296301load
@@ -313,12 +318,12 @@ typeof
313318 => Text
314319 -> Repl e t f m ()
315320typeof args = do
316- st <- get
321+ state <- get
317322 mVal <-
318323 maybe
319324 (exec False line)
320325 (pure . pure )
321- (Data.HashMap.Lazy. lookup (coerce line) (replCtx st ))
326+ (M. lookup (coerce line) (coerce $ replCtx state ))
322327
323328 traverse_ printValueType mVal
324329
@@ -390,7 +395,7 @@ completeFunc reversedPrev word
390395 -- Attributes of sets in REPL context
391396 | var : subFields <- Text. split (== ' .' ) (toText word) , not $ null subFields =
392397 do
393- s <- get
398+ state <- get
394399 maybe
395400 stub
396401 (\ binding ->
@@ -403,15 +408,15 @@ completeFunc reversedPrev word
403408 candidates
404409 )
405410 )
406- (Data.HashMap.Lazy. lookup (coerce var) (replCtx s ))
411+ (M. lookup (coerce var) (coerce $ replCtx state ))
407412
408413 -- Builtins, context variables
409414 | otherwise =
410415 do
411- s <- get
412- let contextKeys = Data.HashMap.Lazy. keys ( replCtx s )
413- (Just (NVSet _ builtins)) = Data.HashMap.Lazy. lookup " builtins" (replCtx s )
414- shortBuiltins = Data.HashMap.Lazy . keys builtins
416+ state <- get
417+ let contextKeys = M. keys @ VarName @ ( NValue t f m ) (coerce $ replCtx state )
418+ (Just (NVSet _ builtins)) = M. lookup " builtins" (coerce $ replCtx state )
419+ shortBuiltins = M . keys builtins
415420
416421 pure $ listCompletion $ toString <$>
417422 [" __includes" ]
@@ -430,7 +435,7 @@ completeFunc reversedPrev word
430435 -> m [Text ]
431436 algebraicComplete subFields val =
432437 let
433- keys = fmap (" ." <> ) . Data.HashMap.Lazy . keys
438+ keys = fmap (" ." <> ) . M . keys
434439
435440 withMap m =
436441 case subFields of
@@ -444,10 +449,10 @@ completeFunc reversedPrev word
444449 ((" ." <> f) <> )
445450 . algebraicComplete fs <=< demand
446451 )
447- (Data.HashMap.Lazy .lookup (coerce f) m)
452+ (M .lookup (coerce f) m)
448453 in
449454 case val of
450- NVSet _ xs -> withMap (Data.HashMap.Lazy . mapKeys coerce xs)
455+ NVSet _ xs -> withMap (M . mapKeys coerce xs)
451456 _ -> stub
452457
453458-- | HelpOption inspired by Dhall Repl
0 commit comments