Skip to content

Commit f7704b4

Browse files
committed
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.
1 parent 4ce176d commit f7704b4

File tree

2 files changed

+24
-6
lines changed

2 files changed

+24
-6
lines changed

main/Main.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -102,7 +102,12 @@ main = do
102102
@(StdThunk (StandardT (StdIdT IO)))
103103
frames
104104

105-
when (repl opts) $ withNixContext Nothing Repl.main
105+
when (repl opts) $
106+
if evaluate opts
107+
then do
108+
val <- Nix.nixEvalExprLoc mpath expr
109+
withNixContext Nothing (Repl.main' $ Just val)
110+
else withNixContext Nothing Repl.main
106111

107112
process opts mpath expr
108113
| evaluate opts

main/Repl.hs

Lines changed: 18 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,10 @@
2020
{-# OPTIONS_GHC -Wno-unused-matches #-}
2121
{-# OPTIONS_GHC -Wno-unused-imports #-}
2222

23-
module Repl where
23+
module Repl
24+
( main
25+
, main'
26+
) where
2427

2528
import Nix hiding ( exec
2629
, try
@@ -60,9 +63,15 @@ import System.Console.Repline ( Cmd
6063
import qualified System.Console.Repline
6164
import qualified System.Exit
6265

66+
-- | Repl entry point
67+
main :: (MonadNix e t f m, MonadIO m, MonadMask m) => m ()
68+
main = main' Nothing
6369

64-
main :: (MonadNix e t f m, MonadIO m, MonadMask m) => m ()
65-
main = flip evalStateT initState
70+
-- | Principled version allowing to pass initial value for context.
71+
--
72+
-- Passed value is stored in context with "input" key.
73+
main' :: (MonadNix e t f m, MonadIO m, MonadMask m) => Maybe (NValue t f m) -> m ()
74+
main' iniVal = flip evalStateT (initState iniVal)
6675
$ System.Console.Repline.evalRepl
6776
banner
6877
cmd
@@ -96,8 +105,12 @@ data IState t f m = IState
96105
, replDbg :: Bool -- ^ Enable REPL debug output, dumping IState on each command
97106
} deriving (Eq, Show)
98107

99-
initState :: MonadIO m => IState t f m
100-
initState = IState Nothing mempty False
108+
initState :: MonadIO m => Maybe (NValue t f m) -> IState t f m
109+
initState mIni =
110+
IState
111+
Nothing
112+
(maybe mempty (\x -> Data.HashMap.Lazy.fromList [("input", x)]) mIni)
113+
False
101114

102115
type Repl e t f m = HaskelineT (StateT (IState t f m) m)
103116

0 commit comments

Comments
 (0)