Skip to content

Commit 5745f44

Browse files
Language.Nix.Identifier: add roundtrip tests with nix-instantiate(1)
We currently test two things marginally different things: 1. If we produce identifier syntax with quote, we verify that Nix will be able to parse and evaluate it and later produce the same quoted identifier as we do. (This makes sure we don't quote unnecessarily.) 2. If we prettyShow an Identifier, we verify that Nix will be able to parse and evaluate it and that we will be able to parse what Nix pretty prints.
1 parent b8f0807 commit 5745f44

File tree

2 files changed

+44
-0
lines changed

2 files changed

+44
-0
lines changed

language-nix/language-nix.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -45,4 +45,5 @@ test-suite hspec
4545
, lens
4646
, parsec-class
4747
, pretty
48+
, process
4849
default-language: Haskell2010

language-nix/test/hspec.hs

Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,14 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
12
module Main (main) where
23

4+
import Control.Exception
35
import Control.Lens
46
import Control.Monad (forM_)
57
import Data.Char (isAscii, isSpace)
8+
import Data.List (dropWhileEnd)
69
import Data.String (fromString)
710
import Language.Nix.Identifier
11+
import System.Process (callProcess, readCreateProcess, proc)
812
import Test.Hspec
913
import Test.QuickCheck
1014
import Text.Parsec.Class (parseM)
@@ -51,10 +55,49 @@ main = hspec $ do
5155
any isSpace s ==> needsQuoting s
5256
it "if length is zero" $ shouldSatisfy "" needsQuoting
5357

58+
describe "nix-instantiate" $ do
59+
nixInstantiate <- runIO $ do
60+
(callProcess nixInstantiateBin [ "--version" ] >> pure (Just nixInstantiateBin))
61+
`catch` (\(_ :: SomeException) -> pure Nothing)
62+
let nix :: Example a => String -> (String -> a) -> SpecWith (Arg a)
63+
nix str spec =
64+
case nixInstantiate of
65+
Nothing -> it str $ \_ ->
66+
pendingWith (nixInstantiateBin ++ " could not be found or executed")
67+
Just exec -> it str $ spec exec
68+
69+
nix "parses and produces result of quote" $ \exec -> stringIdentProperty $ \str -> ioProperty $ do
70+
let expAttr = quote str
71+
expr = "{" ++ expAttr ++ "=null;}"
72+
73+
out <- readCreateProcess (proc exec ["--eval", "--strict", "-E", expr]) ""
74+
pure $ extractIdentSyntax out === expAttr
75+
76+
nix "produces parseM-able identifiers" $ \exec -> identProperty $ \i -> ioProperty $ do
77+
let expr = "{" ++ prettyShow i ++ "=null;}"
78+
out <- readCreateProcess (proc exec ["--eval", "--strict", "-E", expr]) ""
79+
pure $ parseM "Identifier" (extractIdentSyntax out) == Just i
80+
81+
nixInstantiateBin :: String
82+
nixInstantiateBin = "nix-instantiate"
83+
5484
stringIdentProperty :: Testable prop => (String -> prop) -> Property
5585
stringIdentProperty p = property $ \s ->
5686
'\0' `notElem` s ==> classify (needsQuoting s) "need quoting" $ p s
5787

5888
identProperty :: Testable prop => (Identifier -> prop) -> Property
5989
identProperty p = property $ \i ->
6090
classify (needsQuoting (from ident # i)) "need quoting" $ p i
91+
92+
-- | Given the (pretty) printed representation of the Nix value produced by the
93+
-- expression @{ ${ident} = null; }@, for any value of @ident@, extract the
94+
-- part that represents the identifier.
95+
--
96+
-- Note that pretty printing is buggy in some versions of Nix and the result
97+
-- may not actually be valid Nix syntax.
98+
extractIdentSyntax :: String -> String
99+
extractIdentSyntax =
100+
dropWhileEnd (`elem` "= \n\t") -- remove "… = "
101+
. dropWhileEnd (`elem` "null") -- remove "null"
102+
. dropWhileEnd (`elem` ";} \n\t") -- remove "…; }"
103+
. dropWhile (`elem` "{ \n\t") -- remove "{ …"

0 commit comments

Comments
 (0)