Skip to content

Commit

Permalink
Merge #978: Expr: Types: changes
Browse files Browse the repository at this point in the history
  • Loading branch information
Anton-Latukha authored Jul 21, 2021
2 parents f92a283 + a6d9f3e commit dd2d300
Show file tree
Hide file tree
Showing 23 changed files with 373 additions and 277 deletions.
23 changes: 17 additions & 6 deletions ChangeLog.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,10 @@ Partial log (for now):
* Breaking:

* `Nix.Expr.Shorthands`:
* `inherit{,From}`: dropped second argument as irrelevant ([report](https://github.com/haskell-nix/hnix/issues/326)).
* `inherit{,From}`:
* dropped second(/third) argument as irrelevant ([report](https://github.com/haskell-nix/hnix/issues/326))
* bindings to inherit changed type from complex `[NKeyName]` (which is for static & dynamic keys) to `[VarName]` (`VarName` is newtype of `Text`).
* So examples of use now are: `inherit ["a", "b"]`, `inheritFrom (var "a") ["b", "c"]`
* `mkAssert`: fixed ([report](https://github.com/haskell-nix/hnix/issues/969)).
* fx presedence between the operators:

Expand All @@ -25,11 +28,19 @@ Partial log (for now):

* Additional
* `Nix.Expr.Shorthands`:
* `mkOper{,2}` entered deprecation, superceeded by new name `mkOp{,2}`.
* `mkBinop` entered deprecation, supeceeded by new name `mkBinop`.
* added `@.<|>` for Nix language `s.x or y` expession.
* add `mkNeg` number negation.

* added:
* `emptySet`
* `emptyList`
* `mkOp{,2}`
* `mk{,Named,Variadic,General}ParamSet`
* `mkNeg` - number negation.
* `@.<|>` for Nix language `s.x or y` expession.
* entered deprecation:
* `mkOper{,2}` bacame `mkOp{,2}`.
* `mkBinop` became `mkOp2`.
* `mkParaset` supeceeded by `mk{,Named{,Variadic},Variadic,General}ParamSet`.
* fixed:
* `mkAssert` was creating `with`, now properly creates `assert`.

## [(diff)](https://github.com/haskell-nix/hnix/compare/0.13.1...0.14.0#files_bucket) 0.14.0 (2021-07-08)

Expand Down
53 changes: 29 additions & 24 deletions main/Repl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@

{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}

module Repl
( main
Expand All @@ -22,7 +23,7 @@ import Nix.Scope
import Nix.Utils
import Nix.Value.Monad ( demand )

import qualified Data.HashMap.Lazy
import qualified Data.HashMap.Lazy as M
import Data.Char ( isSpace )
import Data.List ( dropWhileEnd )
import qualified Data.Text as Text
Expand Down Expand Up @@ -55,6 +56,7 @@ import System.Console.Repline ( Cmd
import qualified System.Console.Repline as Console
import qualified System.Exit as Exit
import qualified System.IO.Error as Error
import Prelude hiding (state)

-- | Repl entry point
main :: (MonadNix e t f m, MonadIO m, MonadMask m) => m ()
Expand Down Expand Up @@ -136,7 +138,7 @@ main' iniVal =

data IState t f m = IState
{ replIt :: Maybe NExprLoc -- ^ Last expression entered
, replCtx :: AttrSet (NValue t f m) -- ^ Value environment
, replCtx :: Scope (NValue t f m) -- ^ Scope. Value environment.
, replCfg :: ReplConfig -- ^ REPL configuration
} deriving (Eq, Show)

Expand All @@ -159,14 +161,17 @@ initState mIni = do

builtins <- evalText "builtins"

opts :: Nix.Options <- asks (view hasLens)
let
scope = coerce $
M.fromList $
("builtins", builtins) : fmap ("input",) (maybeToList mIni)

opts :: Nix.Options <- asks $ view hasLens

pure $
IState
Nothing
(Data.HashMap.Lazy.fromList $
("builtins", builtins) : fmap ("input",) (maybeToList mIni)
)
scope
defReplConfig
{ cfgStrict = strict opts
, cfgValues = values opts
Expand All @@ -192,9 +197,9 @@ exec
-> Repl e t f m (Maybe (NValue t f m))
exec update source = do
-- Get the current interpreter state
st <- get
state <- get

when (cfgDebug $ replCfg st) $ liftIO $ print st
when (cfgDebug $ replCfg state) $ liftIO $ print state

-- Parser ( returns AST as `NExprLoc` )
case parseExprOrBinding source of
Expand All @@ -211,7 +216,7 @@ exec update source = do
-- let tyctx' = inferTop mempty [("repl", stripAnnotation expr)]
-- liftIO $ print tyctx'

mVal <- lift $ lift $ try $ pushScope (replCtx st) (evalExprLoc expr)
mVal <- lift $ lift $ try $ pushScope (replCtx state) (evalExprLoc expr)

either
(\ (NixException frames) -> do
Expand All @@ -221,11 +226,11 @@ exec update source = do
-- Update the interpreter state
when (update && isBinding) $ do
-- Set `replIt` to last entered expression
put st { replIt = pure expr }
put state { replIt = pure expr }

-- If the result value is a set, update our context with it
case val of
NVSet _ xs -> put st { replCtx = xs <> replCtx st }
NVSet _ (coerce -> scope) -> put state { replCtx = scope <> replCtx state }
_ -> pass

pure $ pure val
Expand Down Expand Up @@ -283,14 +288,14 @@ browse :: (MonadNix e t f m, MonadIO m)
-> Repl e t f m ()
browse _ =
do
st <- get
state <- get
traverse_
(\(k, v) ->
do
liftIO $ Text.putStr $ coerce k <> " = "
printValue v
)
(Data.HashMap.Lazy.toList $ replCtx st)
(M.toList $ coerce $ replCtx state)

-- | @:load@ command
load
Expand All @@ -313,12 +318,12 @@ typeof
=> Text
-> Repl e t f m ()
typeof args = do
st <- get
state <- get
mVal <-
maybe
(exec False line)
(pure . pure)
(Data.HashMap.Lazy.lookup (coerce line) (replCtx st))
(M.lookup (coerce line) (coerce $ replCtx state))

traverse_ printValueType mVal

Expand Down Expand Up @@ -390,7 +395,7 @@ completeFunc reversedPrev word
-- Attributes of sets in REPL context
| var : subFields <- Text.split (== '.') (toText word) , not $ null subFields =
do
s <- get
state <- get
maybe
stub
(\ binding ->
Expand All @@ -403,15 +408,15 @@ completeFunc reversedPrev word
candidates
)
)
(Data.HashMap.Lazy.lookup (coerce var) (replCtx s))
(M.lookup (coerce var) (coerce $ replCtx state))

-- Builtins, context variables
| otherwise =
do
s <- get
let contextKeys = Data.HashMap.Lazy.keys (replCtx s)
(Just (NVSet _ builtins)) = Data.HashMap.Lazy.lookup "builtins" (replCtx s)
shortBuiltins = Data.HashMap.Lazy.keys builtins
state <- get
let contextKeys = M.keys @VarName @(NValue t f m) (coerce $ replCtx state)
(Just (NVSet _ builtins)) = M.lookup "builtins" (coerce $ replCtx state)
shortBuiltins = M.keys builtins

pure $ listCompletion $ toString <$>
["__includes"]
Expand All @@ -430,7 +435,7 @@ completeFunc reversedPrev word
-> m [Text]
algebraicComplete subFields val =
let
keys = fmap ("." <>) . Data.HashMap.Lazy.keys
keys = fmap ("." <>) . M.keys

withMap m =
case subFields of
Expand All @@ -444,10 +449,10 @@ completeFunc reversedPrev word
(("." <> f) <>)
. algebraicComplete fs <=< demand
)
(Data.HashMap.Lazy.lookup (coerce f) m)
(M.lookup (coerce f) m)
in
case val of
NVSet _ xs -> withMap (Data.HashMap.Lazy.mapKeys coerce xs)
NVSet _ xs -> withMap (M.mapKeys coerce xs)
_ -> stub

-- | HelpOption inspired by Dhall Repl
Expand Down
Loading

0 comments on commit dd2d300

Please sign in to comment.