{-# 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 (HorizonOptions (MkHorizonOptions), InputFile (MkInputFile), optInputFile) 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/hashable.nix") , $(mkRelFile "pkgs/Cabal-syntax.nix") , $(mkRelFile "pkgs/network-mux.nix") ] outputFilesPackageSetRel :: [Path Rel File] outputFilesPackageSetRel = [ $(mkRelFile "initial-packages.nix") , $(mkRelFile "pkgs/lens.nix") , $(mkRelFile "pkgs/hashable.nix") , $(mkRelFile "pkgs/Cabal-syntax.nix") , $(mkRelFile "pkgs/network-mux.nix") ] runHorizonGenNixFor :: FilePath -> IO () runHorizonGenNixFor s = do fp <- parseRelFile $ "test/data/" ++ s ++ "/input.dhall" let opts = MkHorizonOptions { optInputFile = MkInputFile fp } horizonGenNix opts expectedOutputTest :: FilePath -> [Path Rel File] -> Spec expectedOutputTest s xs = describe s $ sequential $ aroundAll_ (bracket_ (runHorizonGenNixFor s) (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 expectedOutputTest "modified-package-set" outputFilesPackageSetRel expectedOutputTest "sample-overlay" outputFilesOverlayRel expectedOutputTest "modified-overlay" outputFilesOverlayRel