Implement builtins.currentTime

This commit is contained in:
hsloan 2018-05-02 21:32:00 -07:00 committed by John Wiegley
parent a355366f32
commit c1561ea711
9 changed files with 68 additions and 26 deletions

View File

@ -2,7 +2,7 @@
--
-- see: https://github.com/sol/hpack
--
-- hash: 495fbcc0ec91c76bd2a6f9a571bca3014f7dd68489dc137eb17528a4dfde7a00
-- hash: 3939e6333d509e27377d1de951e2b57efc80952e134d6666a530407b9aa32b3d
name: hnix
version: 0.5.0
@ -118,6 +118,7 @@ library
, template-haskell
, text
, these
, time
, transformers
, unix
, unordered-containers >=0.2.9 && <0.3
@ -158,6 +159,7 @@ executable hnix
, serialise
, template-haskell
, text
, time
, transformers
, unordered-containers >=0.2.9 && <0.3
if flag(tracing)
@ -201,6 +203,7 @@ test-suite hnix-tests
, tasty-th
, template-haskell
, text
, time
, transformers
, unix
, unordered-containers >=0.2.9 && <0.3
@ -234,6 +237,7 @@ benchmark hnix-benchmarks
, serialise
, template-haskell
, text
, time
, transformers
, unordered-containers >=0.2.9 && <0.3
if flag(tracing)

View File

@ -19,6 +19,7 @@ import qualified Data.HashMap.Lazy as M
import qualified Data.Map as Map
import Data.List (sortOn)
import Data.Maybe (fromJust)
import Data.Time
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import qualified Data.Text.Lazy.Encoding as TL
@ -39,7 +40,8 @@ import qualified Text.Show.Pretty as PS
main :: IO ()
main = do
opts <- execParser nixOptionsInfo
time <- liftIO getCurrentTime
opts <- execParser (nixOptionsInfo time)
runLazyM opts $ case readFrom opts of
Just path -> do
let file = addExtension (dropExtension path) "nix"

View File

@ -28,6 +28,7 @@ dependencies:
- serialise
- template-haskell
- text
- time
- transformers
- unordered-containers >= 0.2.9 && < 0.3

View File

@ -23,6 +23,7 @@ module Nix.Builtins (builtins) where
import Control.Monad
import Control.Monad.Catch
import Control.Monad.ListM (sortByM)
import Control.Monad.Reader (asks)
import qualified Crypto.Hash.MD5 as MD5
import qualified Crypto.Hash.SHA1 as SHA1
import qualified Crypto.Hash.SHA256 as SHA256
@ -51,6 +52,7 @@ import Data.Text.Encoding
import qualified Data.Text.Lazy as LazyText
import qualified Data.Text.Lazy.Builder as Builder
import Data.These (fromThese)
import qualified Data.Time.Clock.POSIX as Time
import Data.Traversable (mapM)
import Language.Haskell.TH.Syntax (addDependentFile, runIO)
import Nix.Atoms
@ -62,6 +64,7 @@ import Nix.Expr.Types
import Nix.Expr.Types.Annotated
import Nix.Frames
import Nix.Normal
import Nix.Options
import Nix.Parser
import Nix.Render
import Nix.Scope
@ -122,6 +125,7 @@ builtinsList = sequence [
, add Normal "concatLists" concatLists
, add' Normal "concatStringsSep" (arity2 Text.intercalate)
, add0 Normal "currentSystem" currentSystem
, add0 Normal "currentTime" currentTime_
, add2 Normal "deepSeq" deepSeq
, add0 TopLevel "derivation" $(do
let f = "data/nix/corepkgs/derivation.nix"
@ -929,6 +933,11 @@ currentSystem = do
arch <- getCurrentSystemArch
return $ nvStr (arch <> "-" <> os) mempty
currentTime_ :: MonadNix e m => m (NValue m)
currentTime_ = do
opts :: Options <- asks (view hasLens)
toNix @Integer $ round $ Time.utcTimeToPOSIXSeconds (currentTime opts)
derivationStrict_ :: MonadNix e m => m (NValue m) -> m (NValue m)
derivationStrict_ = (>>= derivationStrict)

View File

@ -5,6 +5,7 @@ import Data.Char (isDigit)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Time
import Options.Applicative hiding (ParserResult(..))
import Text.PrettyPrint.ANSI.Leijen hiding ((<$>))
@ -36,12 +37,13 @@ data Options = Options
, arg :: [(Text, Text)]
, argstr :: [(Text, Text)]
, fromFile :: Maybe FilePath
, currentTime :: UTCTime
, filePaths :: [FilePath]
}
deriving Show
defaultOptions :: Options
defaultOptions = Options
defaultOptions :: UTCTime -> Options
defaultOptions current = Options
{ verbose = ErrorsOnly
, tracing = False
, thunks = False
@ -69,6 +71,7 @@ defaultOptions = Options
, arg = []
, argstr = []
, fromFile = Nothing
, currentTime = current
, filePaths = []
}
@ -96,8 +99,8 @@ argPair = option $ str >>= \s ->
"Format of --arg/--argstr in hnix is: name=expr"
Just i -> return $ second Text.tail $ Text.splitAt i s
nixOptions :: Parser Options
nixOptions = Options
nixOptions :: UTCTime -> Parser Options
nixOptions current = Options
<$> (fromMaybe ErrorsOnly <$>
optional
(option (do a <- str
@ -189,8 +192,13 @@ nixOptions = Options
( short 'f'
<> long "file"
<> help "Parse all of the files given in FILE; - means stdin"))
<*> option (parseTimeOrError True defaultTimeLocale "%Y/%m/%d %H:%M:%S" <$> str)
( long "now"
<> value current
<> help "Set current time for testing purposes")
<*> many (strArgument (metavar "FILE" <> help "Path of file to parse"))
nixOptionsInfo :: ParserInfo Options
nixOptionsInfo = info (helper <*> nixOptions)
(fullDesc <> progDesc "" <> header "hnix")
nixOptionsInfo :: UTCTime -> ParserInfo Options
nixOptionsInfo current =
info (helper <*> nixOptions current)
(fullDesc <> progDesc "" <> header "hnix")

View File

@ -14,6 +14,7 @@ import qualified Data.HashMap.Lazy as M
import Data.Maybe (isJust)
import Data.String.Interpolate.IsString
import Data.Text (Text)
import Data.Time
import Nix
import qualified System.Directory as D
import System.Environment
@ -174,10 +175,12 @@ instance (Show r, Show (NValueF m r), Eq r) => Eq (NValueF m r) where
constantEqual :: NExprLoc -> NExprLoc -> Assertion
constantEqual a b = do
time <- liftIO getCurrentTime
let opts = defaultOptions time
-- putStrLn =<< lint (stripAnnotation a)
a' <- runLazyM defaultOptions $ normalForm =<< nixEvalExprLoc Nothing a
a' <- runLazyM opts $ normalForm =<< nixEvalExprLoc Nothing a
-- putStrLn =<< lint (stripAnnotation b)
b' <- runLazyM defaultOptions $ normalForm =<< nixEvalExprLoc Nothing b
b' <- runLazyM opts $ normalForm =<< nixEvalExprLoc Nothing b
assertEqual "" a' b'
constantEqualText' :: Text -> Text -> Assertion

View File

@ -8,11 +8,13 @@ module Main where
import Control.DeepSeq
import qualified Control.Exception as Exc
import Control.Monad
import Control.Monad.IO.Class
import Data.Fix
import Data.List (isInfixOf)
import Data.Maybe (isJust)
import Data.String.Interpolate.IsString
import Data.Text (unpack)
import Data.Time
import qualified EvalTests
import qualified Nix
import Nix.Exec
@ -57,7 +59,9 @@ ensureNixpkgsCanParse =
url = "https://github.com/NixOS/nixpkgs/archive/#{rev}.tar.gz";
sha256 = "#{sha256}";
}|]) $ \expr -> do
NVStr dir _ <- runLazyM defaultOptions $ Nix.nixEvalExprLoc Nothing expr
NVStr dir _ <- do
time <- liftIO getCurrentTime
runLazyM (defaultOptions time) $ Nix.nixEvalExprLoc Nothing expr
files <- globDir1 (compile "**/*.nix") (unpack dir)
forM_ files $ \file ->
-- Parse and deepseq the resulting expression tree, to ensure the

View File

@ -15,6 +15,7 @@ import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import Data.Time
import GHC.Exts
import Nix.Lint
import Nix.Options
@ -68,12 +69,15 @@ genTests = do
mkTestGroup (kind, tests) =
testGroup (unwords kind) $ map (mkTestCase kind) tests
mkTestCase kind (basename, files) =
testCase (takeFileName basename) $ case kind of
["parse", "okay"] -> assertParse defaultOptions $ the files
["parse", "fail"] -> assertParseFail defaultOptions $ the files
["eval", "okay"] -> assertEval defaultOptions files
["eval", "fail"] -> assertEvalFail $ the files
_ -> error $ "Unexpected: " ++ show kind
testCase (takeFileName basename) $ do
time <- liftIO getCurrentTime
let opts = defaultOptions time
case kind of
["parse", "okay"] -> assertParse opts $ the files
["parse", "fail"] -> assertParseFail opts $ the files
["eval", "okay"] -> assertEval opts files
["eval", "fail"] -> assertEvalFail $ the files
_ -> error $ "Unexpected: " ++ show kind
assertParse :: Options -> FilePath -> Assertion
assertParse _opts file = parseNixFileLoc file >>= \case
@ -105,11 +109,13 @@ assertLangOkXml opts file = do
assertEqual "" expected $ Text.pack actual
assertEval :: Options -> [FilePath] -> Assertion
assertEval _opts files =
assertEval _opts files = do
time <- liftIO getCurrentTime
let opts = defaultOptions time
case delete ".nix" $ sort $ map takeExtensions files of
[] -> () <$ hnixEvalFile defaultOptions (name ++ ".nix")
[".exp"] -> assertLangOk defaultOptions name
[".exp.xml"] -> assertLangOkXml defaultOptions name
[] -> () <$ hnixEvalFile opts (name ++ ".nix")
[".exp"] -> assertLangOk opts name
[".exp.xml"] -> assertLangOkXml opts name
[".exp.disabled"] -> return ()
[".exp-disabled"] -> return ()
[".exp", ".flags"] -> do
@ -117,7 +123,7 @@ assertEval _opts files =
flags <- Text.readFile (name ++ ".flags")
let flags' | Text.last flags == '\n' = Text.init flags
| otherwise = flags
case Opts.execParserPure Opts.defaultPrefs nixOptionsInfo
case Opts.execParserPure Opts.defaultPrefs (nixOptionsInfo time)
(fixup (map Text.unpack (Text.splitOn " " flags'))) of
Opts.Failure err -> errorWithoutStackTrace $
"Error parsing flags from " ++ name ++ ".flags: "
@ -142,7 +148,8 @@ assertEval _opts files =
assertEvalFail :: FilePath -> Assertion
assertEvalFail file = catch ?? (\(_ :: SomeException) -> return ()) $ do
evalResult <- printNix <$> hnixEvalFile defaultOptions file
time <- liftIO getCurrentTime
evalResult <- printNix <$> hnixEvalFile (defaultOptions time) file
evalResult `seq` assertFailure $
file ++ " should not evaluate.\nThe evaluation result was `"
++ evalResult ++ "`."

View File

@ -4,7 +4,9 @@
module TestCommon where
import Control.Monad.Catch
import Control.Monad.IO.Class
import Data.Text (Text, unpack)
import Data.Time
import Nix
import System.Environment
import System.IO
@ -50,13 +52,15 @@ nixEvalFile fp = readProcess "nix-instantiate" ["--eval", fp] ""
assertEvalFileMatchesNix :: FilePath -> Assertion
assertEvalFileMatchesNix fp = do
hnixVal <- (++"\n") . printNix <$> hnixEvalFile defaultOptions fp
time <- liftIO getCurrentTime
hnixVal <- (++"\n") . printNix <$> hnixEvalFile (defaultOptions time) fp
nixVal <- nixEvalFile fp
assertEqual fp nixVal hnixVal
assertEvalMatchesNix :: Text -> Assertion
assertEvalMatchesNix expr = do
hnixVal <- (++"\n") . printNix <$> hnixEvalText defaultOptions expr
time <- liftIO getCurrentTime
hnixVal <- (++"\n") . printNix <$> hnixEvalText (defaultOptions time) expr
nixVal <- nixEvalString expr'
assertEqual expr' nixVal hnixVal
where