Use Void to make an intention clearer

This commit is contained in:
John Wiegley 2018-04-18 13:28:19 -07:00
parent 20ac31db52
commit e7ec507db8
3 changed files with 14 additions and 5 deletions

View file

@ -38,6 +38,7 @@ import Data.Text (Text)
import qualified Data.Text as Text
import Data.These
import Data.Traversable (for)
import Data.Void
import Nix.Atoms
import Nix.Convert
import Nix.Expr
@ -63,7 +64,7 @@ class (Show v, Monad m) => MonadEval v m | v -> m where
evalIf :: v -> m v -> m v -> m v
evalAssert :: v -> m v -> m v
evalApp :: v -> m v -> m v
evalAbs :: Params () -> (m v -> m v) -> m v
evalAbs :: Params Void -> (m v -> m v) -> m v
evalError :: String -> m a
@ -155,12 +156,16 @@ eval (NAbs params body) = do
traceM "NAbs"
scope <- currentScopes @_ @t
traceM $ "Creating lambda abstraction in scope: " ++ show scope
evalAbs (void params) $ \arg ->
evalAbs (clearDefaults params) $ \arg ->
-- jww (2018-04-17): We need to use the bound library here, so that
-- the body is only evaluated once.
withScopes @t scope $ do
args <- buildArgument params arg
pushScope args body
where
clearDefaults :: Params r -> Params Void
clearDefaults (Param name) = Param name
clearDefaults (ParamSet xs b mv) = ParamSet (map (Nothing <$) xs) b mv
-- | If you know that the 'scope' action will result in an 'AttrSet t', then
-- this implementation may be used as an implementation for 'evalWith'.

View file

@ -37,6 +37,7 @@ import Data.List
import Data.STRef
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Void
import Nix.Atoms
import Nix.Context
import Nix.Convert
@ -63,7 +64,7 @@ data NTypeF (m :: * -> *) r
| TStr
| TList r
| TSet (Maybe (HashMap Text r))
| TClosure (Params ()) (m (Symbolic m) -> m (Symbolic m))
| TClosure (Params Void) (m (Symbolic m) -> m (Symbolic m))
| TPath
| TBuiltin String (SThunk m -> m (Symbolic m))
deriving Functor

View file

@ -1,6 +1,8 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
@ -24,6 +26,7 @@ import Data.Monoid (appEndo)
import Data.Text (Text)
import Data.These
import Data.Typeable (Typeable)
import Data.Void
import GHC.Generics
import Nix.Atoms
import Nix.Expr.Types
@ -41,7 +44,7 @@ data NValueF m r
| NVPath FilePath
| NVList [r]
| NVSet (AttrSet r) (AttrSet SourcePos)
| NVClosure (Params ()) (m (NValue m) -> m (NValue m))
| NVClosure (Params Void) (m (NValue m) -> m (NValue m))
-- ^ A function is a closed set of parameters representing the "call
-- signature", used at application time to check the type of arguments
-- passed to the function. Since it supports default values which may
@ -57,7 +60,7 @@ data NValueF m r
-- ^ A builtin function is itself already in normal form. Also, it may
-- or may not choose to evaluate its argument in the production of a
-- result.
deriving (Generic, Typeable, Functor)
deriving (Generic, Typeable, Functor, Foldable, Traversable)
-- | An 'NValueNF' is a fully evaluated value in normal form. An 'NValue m' is
-- a value in head normal form, where only the "top layer" has been