Skip to content

Commit 4fec402

Browse files
wip test against nix-instantiate
1 parent bfb5603 commit 4fec402

File tree

2 files changed

+36
-1
lines changed

2 files changed

+36
-1
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: 35 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,31 @@
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 (dropWhile, dropWhileEnd)
69
import Data.String (fromString)
710
import Language.Nix.Identifier
11+
import System.Exit (ExitCode (..))
12+
import System.Process (callProcess, readCreateProcess, proc)
813
import Test.Hspec
914
import Test.QuickCheck
1015
import Text.Parsec.Class (parseM)
1116
import Text.PrettyPrint.HughesPJClass (prettyShow)
1217

1318
main :: IO ()
14-
main = hspec $ do
19+
main = do
20+
let nixInstantiate = "nix-instantiate"
21+
nixInstantiateWorks <- catch
22+
(callProcess nixInstantiate [ "--version" ] >> pure True)
23+
(\(e :: SomeException) -> pure False)
24+
25+
spec $ if nixInstantiateWorks then Just nixInstantiate else Nothing
26+
27+
spec :: Maybe FilePath -> IO ()
28+
spec nixInstantiate = hspec $ do
1529
describe "Language.Nix.Identifier" $ do
1630
describe "ident" $ do
1731
it "is equivalent to fromString" $
@@ -39,6 +53,26 @@ main = hspec $ do
3953
any isSpace s ==> needsQuoting s
4054
it "if length is zero" $ shouldSatisfy "" needsQuoting
4155

56+
describe "nix-instantiate" $ do
57+
let nit :: Example a => String -> (String -> a) -> SpecWith (Arg a)
58+
nit str spec =
59+
case nixInstantiate of
60+
Nothing -> xit str $ spec undefined
61+
Just exec -> it str $ spec exec
62+
63+
-- TODO: parseM (nix-instantiate (prettyShow i))
64+
nit "test" $ \exec -> stringIdentProperty $ \str -> ioProperty $ do
65+
let expAttr = quote str
66+
extractAttr =
67+
dropWhileEnd (`elem` "= \n\t") -- remove "… = "
68+
. dropWhileEnd (`elem` "null") -- remove "null"
69+
. dropWhileEnd (`elem` ";} \n\t") -- remove "…; }"
70+
. dropWhile (`elem` "{ \n\t") -- remove "{ …"
71+
expr = "{" ++ expAttr ++ "=null;}"
72+
73+
out <- readCreateProcess (proc exec ["--eval", "--strict", "-E", expr]) ""
74+
pure $ extractAttr out === expAttr
75+
4276
stringIdentProperty :: Testable prop => (String -> prop) -> Property
4377
stringIdentProperty p = property $ \s ->
4478
'\0' `notElem` s ==> classify (needsQuoting s) "need quoting" $ p s

0 commit comments

Comments
 (0)