{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Main ( main ) where import Control.Exception (bracket_) import Control.Monad (forM_) import Horizon.Gen.Nix (horizonGenNix) import Horizon.Gen.Nix.Options (Force (MkForce), HorizonCommand (MakePackageSetCommand, OverlayCommand), HorizonOptions (MkHorizonOptions), InputFile (MkInputFile), defaultMakePackageSetOptions, defaultOverlayOptions, defaultPackagesDirectory, optForce, optHorizonCommand, optInputFile, optPackagesDirectory) import Path (File, Path, Rel, mkRelFile, parseRelFile, toFilePath) import System.Directory (removeFile) import Test.Syd (Spec, aroundAll_, describe, doNotRandomiseExecutionOrder, goldenStringFile, it, sequential, sydTest) outputFilesOverlayRel :: [Path Rel File] outputFilesOverlayRel = [ $(mkRelFile "overlay.nix") , $(mkRelFile "pkgs/lens.nix") , $(mkRelFile "pkgs/Cabal-syntax.nix") , $(mkRelFile "pkgs/network-mux.nix") , $(mkRelFile "pkgs/myPackage.nix") ] outputFilesPackageSetRel :: [Path Rel File] outputFilesPackageSetRel = [ $(mkRelFile "initial-packages.nix") , $(mkRelFile "pkgs/lens.nix") , $(mkRelFile "pkgs/Cabal-syntax.nix") , $(mkRelFile "pkgs/network-mux.nix") , $(mkRelFile "pkgs/myPackage.nix") ] runHorizonGenNixFor :: FilePath -> HorizonCommand -> IO () runHorizonGenNixFor s cmd = do fp <- parseRelFile $ "test/data/" ++ s ++ "/input.dhall" let opts = MkHorizonOptions { optHorizonCommand = cmd , optForce = MkForce False , optPackagesDirectory = defaultPackagesDirectory , optInputFile = MkInputFile fp } horizonGenNix opts expectedOutputTest :: FilePath -> [Path Rel File] -> HorizonCommand -> Spec expectedOutputTest s xs cmd = describe s $ sequential $ aroundAll_ (bracket_ (runHorizonGenNixFor s cmd) (mapM_ (removeFile . toFilePath) xs)) $ forM_ xs $ \x -> it (toFilePath x) $ goldenStringFile ("test/data/" ++ s ++ "/output/" ++ toFilePath x ++ ".golden") (readFile $ toFilePath x) main :: IO () main = sydTest $ doNotRandomiseExecutionOrder $ sequential $ do expectedOutputTest "sample-package-set" outputFilesPackageSetRel (MakePackageSetCommand defaultMakePackageSetOptions) expectedOutputTest "modified-package-set" outputFilesPackageSetRel (MakePackageSetCommand defaultMakePackageSetOptions) expectedOutputTest "sample-overlay" outputFilesOverlayRel (OverlayCommand defaultOverlayOptions) expectedOutputTest "modified-overlay" outputFilesOverlayRel (OverlayCommand defaultOverlayOptions)