'import' should never carry over the lexical scope of its parent file

Fixes #334
This commit is contained in:
John Wiegley 2018-08-04 15:08:36 -04:00
parent 705d7c474d
commit 50740972de
No known key found for this signature in database
GPG key ID: C144D8F4F19FE630
4 changed files with 47 additions and 49 deletions

View file

@ -40,29 +40,11 @@ import Nix.Parser
import Nix.Pretty
import Nix.Reduce
import Nix.Render.Frame
import Nix.Scope
import Nix.Thunk
import Nix.Utils
import Nix.Value
import Nix.XML
-- | Evaluate a nix expression in the default context
withNixContext :: forall e m r. (MonadNix e m, Has e Options)
=> Maybe FilePath -> m r -> m r
withNixContext mpath action = do
base <- builtins
opts :: Options <- asks (view hasLens)
let i = value @(NValue m) @(NThunk m) @m $ nvList $
map (value @(NValue m) @(NThunk m) @m
. flip nvStr mempty . Text.pack) (include opts)
pushScope (M.singleton "__includes" i) $
pushScopes base $ case mpath of
Nothing -> action
Just path -> do
traceM $ "Setting __cur_file = " ++ show path
let ref = value @(NValue m) @(NThunk m) @m $ nvPath path
pushScope (M.singleton "__cur_file" ref) action
-- | This is the entry point for all evaluations, whatever the expression tree
-- type. It sets up the common Nix environment and applies the
-- transformations, allowing them to be easily composed.

View file

@ -21,7 +21,7 @@
{-# OPTIONS_GHC -Wno-missing-signatures #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Nix.Builtins (builtins) where
module Nix.Builtins (withNixContext, builtins) where
import Control.Monad
import Control.Monad.Catch
@ -92,6 +92,23 @@ import System.FilePath
import System.Posix.Files
import Text.Regex.TDFA
-- | Evaluate a nix expression in the default context
withNixContext :: forall e m r. (MonadNix e m, Has e Options)
=> Maybe FilePath -> m r -> m r
withNixContext mpath action = do
base <- builtins
opts :: Options <- asks (view hasLens)
let i = value @(NValue m) @(NThunk m) @m $ nvList $
map (value @(NValue m) @(NThunk m) @m
. flip nvStr mempty . Text.pack) (include opts)
pushScope (M.singleton "__includes" i) $
pushScopes base $ case mpath of
Nothing -> action
Just path -> do
traceM $ "Setting __cur_file = " ++ show path
let ref = value @(NValue m) @(NThunk m) @m $ nvPath path
pushScope (M.singleton "__cur_file" ref) action
builtins :: (MonadNix e m, Scoped e (NThunk m) m)
=> m (Scopes m (NThunk m))
builtins = do
@ -759,14 +776,27 @@ isFunction func = func >>= \case
throw_ :: MonadNix e m => m (NValue m) -> m (NValue m)
throw_ = fromValue >=> throwError . ErrorCall . Text.unpack
import_ :: MonadNix e m => m (NValue m) -> m (NValue m)
import_ = fromValue >=> importPath M.empty . getPath
import_ :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
import_ = scopedImport (pure (nvSet M.empty M.empty))
scopedImport :: forall e m. MonadNix e m
=> m (NValue m) -> m (NValue m) -> m (NValue m)
scopedImport aset path =
fromValue aset >>= \s ->
fromValue path >>= \p -> importPath @m s (getPath p)
scopedImport asetArg pathArg =
fromValue @(AttrSet (NThunk m)) asetArg >>= \s ->
fromValue pathArg >>= \(Path p) -> do
path <- pathToDefaultNix p
mres <- lookupVar @_ @(NThunk m) "__cur_file"
path' <- case mres of
Nothing -> do
traceM "No known current directory"
return path
Just p -> fromValue @_ @_ @(NThunk m) p >>= \(Path p') -> do
traceM $ "Current file being evaluated is: " ++ show p'
return $ takeDirectory p' </> path
clearScopes @(NThunk m) $
withNixContext (Just path') $
pushScope s $
importPath @m path'
getEnv_ :: MonadNix e m => m (NValue m) -> m (NValue m)
getEnv_ = fromValue >=> \s -> do

View file

@ -24,7 +24,8 @@ class MonadFile m => MonadEffects m where
findPath :: [NThunk m] -> FilePath -> m FilePath
pathExists :: FilePath -> m Bool
importPath :: AttrSet (NThunk m) -> FilePath -> m (NValue m)
importPath :: FilePath -> m (NValue m)
pathToDefaultNix :: FilePath -> m FilePath
getEnvVar :: String -> m (Maybe String)
getCurrentSystemOS :: m Text

View file

@ -531,6 +531,9 @@ instance (MonadFix m, MonadCatch m, MonadIO m, Alternative m,
pure $ cwd <///> origPathExpanded
liftIO $ removeDotDotIndirections <$> canonicalizePath absPath
-- Given a path, determine the nix file to load
pathToDefaultNix = liftIO . pathToDefaultNixFile
findEnvPath = findEnvPathM
findPath = findPathM
@ -542,41 +545,23 @@ instance (MonadFix m, MonadCatch m, MonadIO m, Alternative m,
(fileExist fp)
(\ _ -> return False)
importPath scope origPath = do
path <- liftIO $ pathToDefaultNixFile origPath
mres <- lookupVar @(Context (Lazy m) (NThunk (Lazy m)))
"__cur_file"
path' <- case mres of
Nothing -> do
traceM "No known current directory"
return path
Just p -> fromValue @_ @_ @(NThunk (Lazy m)) p >>= \(Path p') -> do
traceM $ "Current file being evaluated is: " ++ show p'
return $ takeDirectory p' </> path
traceM $ "Importing file " ++ path'
withFrame Info (ErrorCall $ "While importing file " ++ show path') $ do
importPath path = do
traceM $ "Importing file " ++ path
withFrame Info (ErrorCall $ "While importing file " ++ show path) $ do
imports <- Lazy $ ReaderT $ const get
expr <- case M.lookup path' imports of
evalExprLoc =<< case M.lookup path imports of
Just expr -> pure expr
Nothing -> do
eres <- Lazy $ parseNixFileLoc path'
eres <- Lazy $ parseNixFileLoc path
case eres of
Failure err ->
throwError $ ErrorCall . show $
text "Parse during import failed:" P.</> err
Success expr -> do
Lazy $ ReaderT $ const $
modify (M.insert origPath expr)
modify (M.insert path expr)
pure expr
let ref = value @_ @_ @(Lazy m) (nvPath path')
-- Use this cookie so that when we evaluate the next
-- import, we'll remember which directory its containing
-- file was in.
pushScope (M.singleton "__cur_file" ref) $
pushScope scope $ evalExprLoc expr
getEnvVar = liftIO . lookupEnv
getCurrentSystemOS = return $ Text.pack System.Info.os