@@ -17,7 +17,6 @@ module Repl
1717import Prelude hiding ( state )
1818import Nix hiding ( exec )
1919import Nix.Scope
20- import Nix.Utils
2120import Nix.Value.Monad ( demand )
2221
2322import qualified Data.HashMap.Lazy as M
@@ -268,11 +267,15 @@ printValue :: (MonadNix e t f m, MonadIO m)
268267 -> Repl e t f m ()
269268printValue val = do
270269 cfg <- replCfg <$> get
270+ let
271+ g :: MonadIO m => Doc ann0 -> m ()
272+ g = liftIO . print
273+
271274 lift $ lift $
272275 (if
273- | cfgStrict cfg -> liftIO . print . prettyNValue <=< normalForm
274- | cfgValues cfg -> liftIO . print . prettyNValueProv <=< removeEffects
275- | otherwise -> liftIO . print . prettyNValue <=< removeEffects
276+ | cfgStrict cfg -> g . prettyNValue <=< normalForm
277+ | cfgValues cfg -> g . prettyNValueProv <=< removeEffects
278+ | otherwise -> g . prettyNValue <=< removeEffects
276279 ) val
277280
278281
@@ -297,16 +300,15 @@ browse _ =
297300load
298301 :: (MonadNix e t f m , MonadIO m )
299302 -- This one does I String -> O String pretty fast, it is ugly to double marshall here.
300- => String
303+ => Path
301304 -> Repl e t f m ()
302- load args =
305+ load path =
303306 do
304- contents <- liftIO $
305- Text. readFile $
306- trim args
307+ contents <- liftIO $ Prelude. readFile $
308+ trim path
307309 void $ exec True contents
308310 where
309- trim = dropWhileEnd isSpace . dropWhile isSpace
311+ trim = dropWhileEnd isSpace . dropWhile isSpace . coerce
310312
311313-- | @:type@ command
312314typeof
@@ -404,14 +406,20 @@ completeFunc reversedPrev word
404406 candidates
405407 )
406408 )
407- (M. lookup (coerce var) ( coerce $ replCtx state) )
409+ (M. lookup (coerce var) $ coerce $ replCtx state)
408410
409411 -- Builtins, context variables
410412 | otherwise =
411413 do
412414 state <- get
413- let contextKeys = M. keys @ VarName @ (NValue t f m ) (coerce $ replCtx state)
414- (Just (NVSet _ builtins)) = M. lookup " builtins" (coerce $ replCtx state)
415+ let
416+ scopeHashMap :: HashMap VarName (NValue t f m )
417+ scopeHashMap = coerce $ replCtx state
418+ contextKeys :: [VarName ]
419+ contextKeys = M. keys scopeHashMap
420+ builtins :: AttrSet (NValue t f m )
421+ (Just (NVSet _ builtins)) = M. lookup " builtins" scopeHashMap
422+ shortBuiltins :: [VarName ]
415423 shortBuiltins = M. keys builtins
416424
417425 pure $ listCompletion $ toString <$>
@@ -468,7 +476,7 @@ helpOptions =
468476 " help"
469477 " "
470478 " Print help text"
471- (help helpOptions . toText )
479+ (help helpOptions . fromString )
472480 , HelpOption
473481 " paste"
474482 " "
@@ -478,17 +486,17 @@ helpOptions =
478486 " load"
479487 " FILENAME"
480488 " Load .nix file into scope"
481- load
489+ ( load . fromString)
482490 , HelpOption
483491 " browse"
484492 " "
485493 " Browse bindings in interpreter context"
486- (browse . toText )
494+ (browse . fromString )
487495 , HelpOption
488496 " type"
489497 " EXPRESSION"
490498 " Evaluate expression or binding from context and print the type of the result value"
491- (typeof . toText )
499+ (typeof . fromString )
492500 , HelpOption
493501 " quit"
494502 " "
@@ -503,7 +511,7 @@ helpOptions =
503511 <> Prettyprinter. line
504512 <> renderSetOptions helpSetOptions
505513 )
506- (setConfig . toText )
514+ (setConfig . fromString )
507515 ]
508516
509517-- | Options for :set
0 commit comments