Move the scoping code into its own module

This commit is contained in:
John Wiegley 2018-03-30 13:30:28 -07:00
parent 0b812d5c94
commit 5effdda04b
7 changed files with 78 additions and 71 deletions

View file

@ -45,3 +45,10 @@ atomToEnvString = \case
NBool False -> ""
NNull -> ""
NUri uri -> uri
-- | Translate an atom into its nix representation.
atomText :: NAtom -> Text
atomText (NInt i) = pack (show i)
atomText (NBool b) = if b then "true" else "false"
atomText NNull = "null"
atomText (NUri uri) = uri

View file

@ -25,6 +25,7 @@ import Data.Foldable (foldlM)
import Data.Traversable (mapM)
import Nix.Atoms
import Nix.Eval
import Nix.Scope
import Nix.Expr (NExpr)
import Nix.Parser
import Nix.Utils

View file

@ -8,13 +8,10 @@
{-# LANGUAGE TypeFamilies #-}
module Nix.Eval
(NValue, NValueNF, NValueF(..), ValueSet, MonadNix(..),
StorePath (..), NestedScopes(..), scopeLookup, combineScopes,
extendScope, emptyScopes, newScope, newWeakScope,
(NValue, NValueNF, NValueF(..), ValueSet, MonadNix(..), StorePath (..),
evalExpr, tracingExprEval, evalBinds, exprNormalForm, normalForm,
builtin, builtin2, builtin3, atomText, valueText, buildArgument) where
import Control.Applicative
import Control.Monad hiding (mapM, sequence)
import Control.Monad.Fix
import Control.Monad.IO.Class
@ -25,7 +22,7 @@ import Data.Functor.Identity
import Data.List (intercalate)
import qualified Data.Map.Lazy as Map
import Data.Maybe (fromMaybe)
import Data.Monoid (appEndo, Endo)
import Data.Monoid (appEndo)
import Data.Text (Text)
import qualified Data.Text as Text
import Data.These
@ -33,11 +30,10 @@ import Data.Typeable (Typeable)
import GHC.Generics
import Nix.Atoms
import Nix.Expr
import Nix.Scope
import Nix.StringOperations (runAntiquoted)
import Nix.Utils
type DList a = Endo [a]
-- | An 'NValue' is the most reduced form of an 'NExpr' after evaluation
-- is completed.
data NValueF m r
@ -76,7 +72,6 @@ data NValueF m r
type NValueNF m = Fix (NValueF m) -- normal form
type NValue m = NValueF m (NThunk m) -- head normal form
type ValueSet m = Map.Map Text (NThunk m)
instance Show f => Show (NValueF m f) where
@ -103,19 +98,6 @@ instance Show f => Show (NValueF m f) where
. showString " "
. showsPrec 11 b
builtin :: MonadNix m => String -> (NThunk m -> m (NValue m)) -> m (NValue m)
builtin name f = return $ NVBuiltin name f
builtin2 :: MonadNix m
=> String -> (NThunk m -> NThunk m -> m (NValue m)) -> m (NValue m)
builtin2 name f = builtin name (builtin name . f)
builtin3 :: MonadNix m
=> String -> (NThunk m -> NThunk m -> NThunk m -> m (NValue m))
-> m (NValue m)
builtin3 name f =
builtin name $ \a -> builtin name $ \b -> builtin name $ \c -> f a b c
valueText :: forall m. MonadNix m => NValueNF m -> m (Text, DList Text)
valueText = cata phi where
phi :: NValueF m (m (Text, DList Text)) -> m (Text, DList Text)
@ -141,60 +123,22 @@ valueText = cata phi where
valueTextNoContext :: MonadNix m => NValueNF m -> m Text
valueTextNoContext = fmap fst . valueText
-- | Translate an atom into its nix representation.
atomText :: NAtom -> Text
atomText (NInt i) = Text.pack (show i)
atomText (NBool b) = if b then "true" else "false"
atomText NNull = "null"
atomText (NUri uri) = uri
builtin :: MonadNix m => String -> (NThunk m -> m (NValue m)) -> m (NValue m)
builtin name f = return $ NVBuiltin name f
builtin2 :: MonadNix m
=> String -> (NThunk m -> NThunk m -> m (NValue m)) -> m (NValue m)
builtin2 name f = builtin name (builtin name . f)
builtin3 :: MonadNix m
=> String -> (NThunk m -> NThunk m -> NThunk m -> m (NValue m))
-> m (NValue m)
builtin3 name f =
builtin name $ \a -> builtin name $ \b -> builtin name $ \c -> f a b c
-- | A path into the nix store
newtype StorePath = StorePath { unStorePath :: FilePath }
data Scope a = Scope
{ _scopeMap :: Map.Map Text a
, scopeWeak :: Bool
}
deriving Functor
instance Show (Scope a) where
show (Scope xs _) = show $ Map.keys xs
newScope :: Map.Map Text a -> Scope a
newScope m = Scope m False
newWeakScope :: Map.Map Text a -> Scope a
newWeakScope m = Scope m True
newtype NestedScopes a = NestedScopes { getNestedScopes :: [Scope a] }
deriving Functor
instance Show (NestedScopes a) where
show (NestedScopes xs) = show xs
emptyScopes :: NestedScopes a
emptyScopes = NestedScopes []
scopeLookup :: Text -> NestedScopes a -> Maybe a
scopeLookup key = para go Nothing . getNestedScopes
where
go (Scope m True) ms rest =
-- If the symbol lookup is in a weak scope, first see if there are any
-- matching symbols from the *non-weak* scopes after this one. If so,
-- prefer that, otherwise perform the lookup here. This way, if there
-- are several weaks scopes in a row, followed by non-weak scopes,
-- we'll first prefer the symbol from the non-weak scopes, and then
-- prefer it from the first weak scope that matched.
scopeLookup key (NestedScopes (filter (not . scopeWeak) ms))
<|> Map.lookup key m <|> rest
go (Scope m False) _ rest = Map.lookup key m <|> rest
combineScopes :: NestedScopes a -> NestedScopes a -> NestedScopes a
combineScopes (NestedScopes xs) (NestedScopes ys) = NestedScopes (xs ++ ys)
extendScope :: Map.Map Text a -> NestedScopes a -> NestedScopes a
extendScope x (NestedScopes xs) = NestedScopes (newScope x:xs)
class MonadFix m => MonadNix m where
currentScope :: m (NestedScopes (NThunk m))
clearScopes :: m r -> m r

View file

@ -10,6 +10,7 @@ import Nix.Atoms
import Nix.Builtins
import Nix.Eval
import Nix.Expr
import Nix.Scope
nullVal :: MonadNix m => m (NValue m)
nullVal = return $ NVConstant NNull

50
Nix/Scope.hs Normal file
View file

@ -0,0 +1,50 @@
module Nix.Scope where
import Control.Applicative
import qualified Data.Map.Lazy as Map
import Data.Text (Text)
import Nix.Utils
data Scope a = Scope
{ _scopeMap :: Map.Map Text a
, scopeWeak :: Bool
}
deriving Functor
instance Show (Scope a) where
show (Scope xs _) = show $ Map.keys xs
newScope :: Map.Map Text a -> Scope a
newScope m = Scope m False
newWeakScope :: Map.Map Text a -> Scope a
newWeakScope m = Scope m True
newtype NestedScopes a = NestedScopes { getNestedScopes :: [Scope a] }
deriving Functor
instance Show (NestedScopes a) where
show (NestedScopes xs) = show xs
emptyScopes :: NestedScopes a
emptyScopes = NestedScopes []
scopeLookup :: Text -> NestedScopes a -> Maybe a
scopeLookup key = para go Nothing . getNestedScopes
where
go (Scope m True) ms rest =
-- If the symbol lookup is in a weak scope, first see if there are any
-- matching symbols from the *non-weak* scopes after this one. If so,
-- prefer that, otherwise perform the lookup here. This way, if there
-- are several weaks scopes in a row, followed by non-weak scopes,
-- we'll first prefer the symbol from the non-weak scopes, and then
-- prefer it from the first weak scope that matched.
scopeLookup key (NestedScopes (filter (not . scopeWeak) ms))
<|> Map.lookup key m <|> rest
go (Scope m False) _ rest = Map.lookup key m <|> rest
combineScopes :: NestedScopes a -> NestedScopes a -> NestedScopes a
combineScopes (NestedScopes xs) (NestedScopes ys) = NestedScopes (xs ++ ys)
extendScope :: Map.Map Text a -> NestedScopes a -> NestedScopes a
extendScope x (NestedScopes xs) = NestedScopes (newScope x:xs)

View file

@ -6,6 +6,7 @@ module Nix.Utils (module Nix.Utils, module X) where
import Control.Monad
import Control.Monad.Fix
import Data.Fix
import Data.Monoid (appEndo, Endo)
#define ENABLE_TRACING 1
#if ENABLE_TRACING
@ -18,6 +19,8 @@ traceM :: Monad m => String -> m ()
traceM = const (return ())
#endif
type DList a = Endo [a]
(&) :: a -> (a -> c) -> c
(&) = flip ($)

View file

@ -23,6 +23,7 @@ Library
Default-language: Haskell2010
Exposed-modules:
Nix.Atoms
Nix.Scope
Nix.Eval
Nix.Lint
Nix.Builtins