Run the repl in the same MonadNix environment as Main.hs

Fixes #204
This commit is contained in:
John Wiegley 2018-04-28 16:13:24 -07:00
parent 1093c1ff6e
commit 100c41db6d
7 changed files with 37 additions and 28 deletions

View file

@ -2,7 +2,7 @@
--
-- see: https://github.com/sol/hpack
--
-- hash: f2849e05edde8ddd3f02ee010be0fa0e7ee673392948670ced6209113f5b5e7f
-- hash: ee56fd6136ce0db148efb227049d29b4f4e50599ad21a1035d87571abea00b97
name: hnix
version: 0.5.0
@ -95,6 +95,7 @@ library
, exceptions
, filepath
, hashable
, haskeline
, megaparsec
, monadlist
, mtl
@ -139,6 +140,7 @@ executable hnix
, deepseq
, exceptions
, filepath
, haskeline
, hnix
, mtl
, optparse-applicative

View file

@ -46,7 +46,7 @@ main = do
mapM_ (processFile opts)
=<< (lines <$> liftIO (readFile path))
Nothing -> case filePaths opts of
[] -> liftIO $ Repl.shell (pure ())
[] -> Repl.shell (pure ())
["-"] ->
handleResult opts Nothing . parseNixTextLoc
=<< liftIO Text.getContents
@ -73,7 +73,7 @@ main = do
errorWithoutStackTrace . show
=<< renderFrames @(NThunk (Lazy IO)) frames
when (repl opts) $ liftIO $ Repl.shell (pure ())
when (repl opts) $ Repl.shell (pure ())
process opts mpath expr = do
let printer :: (MonadNix e m, MonadIO m) => NValue m -> m ()

View file

@ -10,6 +10,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeSynonymInstances #-}
@ -25,21 +26,20 @@ import qualified Nix.Type.Env as Env
import Nix.Type.Infer
import qualified Data.HashMap.Lazy as M
import Data.List (isPrefixOf, foldl')
import qualified Data.Map as Map
import Data.Monoid
import Data.Text (unpack, pack)
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import Control.Monad.Identity
import Control.Monad.State.Strict
import Data.List (isPrefixOf, foldl')
import Data.Text (unpack, pack)
import qualified Data.Text as Text
import System.Exit
import System.Environment
import System.Console.Haskeline.MonadException
import System.Console.Repline
import System.Environment
import System.Exit
-------------------------------------------------------------------------------
-- Types
@ -56,8 +56,8 @@ data IState = IState
initState :: IState
initState = IState {-Env.empty-} undefined
type Repl a = HaskelineT (StateT IState IO) a
hoistErr :: Result a -> Repl a
type Repl e m a = HaskelineT (StateT IState m) a
hoistErr :: MonadIO m => Result a -> Repl e m a
hoistErr (Success val) = return val
hoistErr (Failure err) = do
liftIO $ print err
@ -67,7 +67,7 @@ hoistErr (Failure err) = do
-- Execution
-------------------------------------------------------------------------------
exec :: Bool -> Text.Text -> Repl ()
exec :: forall e m. (MonadNix e m, MonadIO m) => Bool -> Text.Text -> Repl e m ()
exec update source = do
-- Get the current interpreter state
st <- get
@ -87,14 +87,13 @@ exec update source = do
when update (put st')
-- If a value is entered, print it.
val <- liftIO $ runLazyM defaultOptions $
val <-
-- jww (2018-04-12): Once the user is able to establish definitions
-- in the repl, they should be passed here.
pushScope @(NThunk (Lazy IO)) M.empty $
nixEvalExprLoc Nothing expr
lift $ lift $ pushScope @(NThunk m) M.empty $ evalExprLoc expr
liftIO $ print val
cmd :: String -> Repl ()
cmd :: (MonadNix e m, MonadIO m) => String -> Repl e m ()
cmd source = exec True (Text.pack source)
-------------------------------------------------------------------------------
@ -102,20 +101,20 @@ cmd source = exec True (Text.pack source)
-------------------------------------------------------------------------------
-- :browse command
browse :: [String] -> Repl ()
browse :: MonadNix e m => [String] -> Repl e m ()
browse _ = do
st <- get
undefined
-- liftIO $ mapM_ putStrLn $ ppenv (tyctx st)
-- :load command
load :: [String] -> Repl ()
load :: (MonadNix e m, MonadIO m) => [String] -> Repl e m ()
load args = do
contents <- liftIO $ Text.readFile (unwords args)
exec True contents
-- :type command
-- typeof :: [String] -> Repl ()
-- typeof :: [String] -> Repl e m ()
-- typeof args = do
-- st <- get
-- let arg = unwords args
@ -124,7 +123,7 @@ load args = do
-- Nothing -> exec False (Text.pack arg)
-- :quit command
quit :: a -> Repl ()
quit :: (MonadNix e m, MonadIO m) => a -> Repl e m ()
quit _ = liftIO exitSuccess
-------------------------------------------------------------------------------
@ -146,7 +145,7 @@ comp n = do
-- let defs = map unpack $ Map.keys ctx
return $ filter (isPrefixOf n) (cmds {-++ defs-})
options :: [(String, [String] -> Repl ())]
options :: (MonadNix e m, MonadIO m) => [(String, [String] -> Repl e m ())]
options = [
("load" , load)
, ("browse" , browse)
@ -158,10 +157,10 @@ options = [
-- Entry Point
-------------------------------------------------------------------------------
completer :: CompleterStyle (StateT IState IO)
completer :: (MonadNix e m, MonadIO m) => CompleterStyle (StateT IState m)
completer = Prefix (wordCompleter comp) defaultMatcher
shell :: Repl a -> IO ()
shell :: (MonadNix e m, MonadIO m, MonadException m) => Repl e m a -> m ()
shell pre = flip evalStateT initState $
evalRepl "hnix> " cmd options completer pre

View file

@ -68,6 +68,7 @@ library:
- deriving-compat >= 0.3 && < 0.5
- directory
- hashable
- haskeline
- megaparsec
- monadlist
- pretty-show
@ -91,6 +92,7 @@ executables:
- hnix
- aeson
- repline
- haskeline
tests:
hnix-tests:

View file

@ -23,7 +23,7 @@ import Control.Arrow (first)
import Control.Monad
import Control.Monad.Fix
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.State.Strict
import Data.Align.Key
import Data.Fix
import Data.HashMap.Lazy (HashMap)

View file

@ -31,9 +31,9 @@ import Control.Monad.Catch
import Control.Monad.Fix
import Control.Monad.IO.Class
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.State.Strict
import Control.Monad.Trans.Reader (ReaderT(..))
import Control.Monad.Trans.State (StateT(..))
import Control.Monad.Trans.State.Strict (StateT(..))
import qualified Data.ByteString as BS
import Data.Coerce
import Data.Fix
@ -62,6 +62,7 @@ import Nix.Scope
import Nix.Thunk
import Nix.Utils
import Nix.Value
import System.Console.Haskeline.MonadException hiding (catch)
import System.Directory
import System.Environment
import System.Exit (ExitCode (ExitSuccess))
@ -432,6 +433,11 @@ instance MonadCatch m => MonadCatch (Lazy m) where
instance MonadThrow m => MonadThrow (Lazy m) where
throwM = Lazy . throwM
instance MonadException m => MonadException (Lazy m) where
controlIO f = Lazy $ controlIO $ \(RunIO run) ->
let run' = RunIO (fmap Lazy . run . runLazy)
in fmap runLazy $ f run'
instance (MonadFix m, MonadCatch m, MonadThrow m, MonadIO m,
Alternative m, MonadPlus m, Typeable m)
=> MonadEffects (Lazy m) where

View file

@ -39,9 +39,9 @@ import Control.Monad.Catch
import Control.Monad.Fix
import Control.Monad.IO.Class
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.State.Strict
import Control.Monad.Trans.Reader (ReaderT(..))
import Control.Monad.Trans.State (StateT(..))
import Control.Monad.Trans.State.Strict (StateT(..))
import Data.Fix
import Data.Foldable
import Data.HashMap.Lazy (HashMap)