File: NixSpec.hs

package info (click to toggle)
haskell-stack 2.15.7-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 3,568 kB
  • sloc: haskell: 37,057; makefile: 6; ansic: 5
file content (115 lines) | stat: -rw-r--r-- 5,222 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
{-# LANGUAGE NoImplicitPrelude     #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedRecordDot   #-}
{-# LANGUAGE OverloadedStrings     #-}

module Stack.NixSpec
  ( sampleConfigNixEnabled
  , sampleConfigNixDisabled
  , setup
  , spec
  ) where

import           Data.Maybe ( fromJust )
import           Options.Applicative
                   ( defaultPrefs, execParserPure, getParseResult, info )
import           Prelude ( writeFile )
import           Stack.Config ( loadConfig )
import           Stack.Config.Nix ( nixCompiler )
import           Stack.Constants ( osIsWindows, stackDotYaml )
import           Stack.Options.GlobalParser ( globalOptsFromMonoid )
import           Stack.Options.NixParser ( nixOptsParser )
import           Stack.Prelude
import           Stack.Runners ( withRunnerGlobal )
import           Stack.Types.Config ( Config (..) )
import           Stack.Types.ConfigMonoid ( ConfigMonoid (..) )
import qualified Stack.Types.GlobalOpts as GlobalOpts ( GlobalOpts (..) )
import           Stack.Types.GlobalOptsMonoid ( GlobalOptsMonoid (..) )
import           Stack.Types.Nix ( NixOpts (..) )
import           System.Directory ( getCurrentDirectory, setCurrentDirectory )
import           System.Environment ( unsetEnv )
import           Test.Hspec ( Spec, around_, beforeAll, describe, it, shouldBe )

sampleConfigNixEnabled :: String
sampleConfigNixEnabled =
  "snapshot: lts-19.22\n" ++
  "packages: ['.']\n" ++
  "system-ghc: true\n" ++
  "nix:\n" ++
  "   enable: True\n" ++
  "   packages: [glpk]"

sampleConfigNixDisabled :: String
sampleConfigNixDisabled =
  "snapshot: lts-19.22\n" ++
  "packages: ['.']\n" ++
  "nix:\n" ++
  "   enable: False"

setup :: IO ()
setup = unsetEnv "STACK_YAML"

spec :: Spec
spec = beforeAll setup $ do
  let loadConfig' :: ConfigMonoid -> (Config -> IO ()) -> IO ()
      loadConfig' cmdLineArgs inner = do
        globalOpts <- globalOptsFromMonoid False mempty { configMonoid = cmdLineArgs }
        withRunnerGlobal globalOpts { GlobalOpts.logLevel = LevelOther "silent" } $
          loadConfig (liftIO . inner)
      inTempDir test = do
        currentDirectory <- getCurrentDirectory
        withSystemTempDirectory "Stack_ConfigSpec" $ \tempDir -> do
          let enterDir = setCurrentDirectory tempDir
              exitDir = setCurrentDirectory currentDirectory
          bracket_ enterDir exitDir test
      withStackDotYaml config test = inTempDir $ do
        writeFile (toFilePath stackDotYaml) config
        test
      parseNixOpts cmdLineOpts = fromJust $ getParseResult $ execParserPure
        defaultPrefs
        (info (nixOptsParser False) mempty)
        cmdLineOpts
      parseOpts cmdLineOpts = mempty { nixOpts = parseNixOpts cmdLineOpts }
  let trueOnNonWindows = not osIsWindows
  describe "nix disabled in config file" $
    around_ (withStackDotYaml sampleConfigNixDisabled) $ do
      it "sees that the nix shell is not enabled" $ loadConfig' mempty $ \config ->
         config.nix.enable `shouldBe` False
      describe "--nix given on command line" $
        it "sees that the nix shell is enabled" $
          loadConfig' (parseOpts ["--nix"]) $ \config ->
          config.nix.enable `shouldBe` trueOnNonWindows
      describe "--nix-pure given on command line" $
        it "sees that the nix shell is enabled" $
          loadConfig' (parseOpts ["--nix-pure"]) $ \config ->
          config.nix.enable `shouldBe` trueOnNonWindows
      describe "--no-nix given on command line" $
        it "sees that the nix shell is not enabled" $
          loadConfig' (parseOpts ["--no-nix"]) $ \config ->
          config.nix.enable `shouldBe` False
      describe "--no-nix-pure given on command line" $
        it "sees that the nix shell is not enabled" $
          loadConfig' (parseOpts ["--no-nix-pure"]) $ \config ->
          config.nix.enable `shouldBe` False
  describe "nix enabled in config file" $
    around_ (withStackDotYaml sampleConfigNixEnabled) $ do
      it "sees that the nix shell is enabled" $
        loadConfig' mempty $ \config ->
        config.nix.enable `shouldBe` trueOnNonWindows
      describe "--no-nix given on command line" $
        it "sees that the nix shell is not enabled" $
          loadConfig' (parseOpts ["--no-nix"]) $ \config ->
          config.nix.enable `shouldBe` False
      describe "--nix-pure given on command line" $
        it "sees that the nix shell is enabled" $
          loadConfig' (parseOpts ["--nix-pure"]) $ \config ->
          config.nix.enable `shouldBe` trueOnNonWindows
      describe "--no-nix-pure given on command line" $
        it "sees that the nix shell is enabled" $
          loadConfig' (parseOpts ["--no-nix-pure"]) $ \config ->
          config.nix.enable `shouldBe` trueOnNonWindows
      it "sees that the only package asked for is glpk and asks for the correct GHC derivation" $ loadConfig' mempty $ \config -> do
        config.nix.packages `shouldBe` ["glpk"]
        v <- parseVersionThrowing "9.0.2"
        ghc <- either throwIO pure $ nixCompiler (WCGhc v)
        ghc `shouldBe` "haskell.compiler.ghc902"