repl: Pass result of --eval -E "..expr.." to REPL

Allows us to do
```
hnix --eval -E '{ a = 2; b = "test"; }' --repl

hnix> :browse
input = { a = 2; b = "test"; }
hnix> input.a
2
hnix> input.b
"test"
```

Closes #292.
This commit is contained in:
Richard Marko 2020-06-30 14:13:47 +02:00
parent 4ce176d1a1
commit f7704b4c28
2 changed files with 24 additions and 6 deletions

View File

@ -102,7 +102,12 @@ main = do
@(StdThunk (StandardT (StdIdT IO)))
frames
when (repl opts) $ withNixContext Nothing Repl.main
when (repl opts) $
if evaluate opts
then do
val <- Nix.nixEvalExprLoc mpath expr
withNixContext Nothing (Repl.main' $ Just val)
else withNixContext Nothing Repl.main
process opts mpath expr
| evaluate opts

View File

@ -20,7 +20,10 @@
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-unused-imports #-}
module Repl where
module Repl
( main
, main'
) where
import Nix hiding ( exec
, try
@ -60,9 +63,15 @@ import System.Console.Repline ( Cmd
import qualified System.Console.Repline
import qualified System.Exit
-- | Repl entry point
main :: (MonadNix e t f m, MonadIO m, MonadMask m) => m ()
main = main' Nothing
main :: (MonadNix e t f m, MonadIO m, MonadMask m) => m ()
main = flip evalStateT initState
-- | Principled version allowing to pass initial value for context.
--
-- Passed value is stored in context with "input" key.
main' :: (MonadNix e t f m, MonadIO m, MonadMask m) => Maybe (NValue t f m) -> m ()
main' iniVal = flip evalStateT (initState iniVal)
$ System.Console.Repline.evalRepl
banner
cmd
@ -96,8 +105,12 @@ data IState t f m = IState
, replDbg :: Bool -- ^ Enable REPL debug output, dumping IState on each command
} deriving (Eq, Show)
initState :: MonadIO m => IState t f m
initState = IState Nothing mempty False
initState :: MonadIO m => Maybe (NValue t f m) -> IState t f m
initState mIni =
IState
Nothing
(maybe mempty (\x -> Data.HashMap.Lazy.fromList [("input", x)]) mIni)
False
type Repl e t f m = HaskelineT (StateT (IState t f m) m)