{-# LANGUAGE RecordWildCards #-} module Horizon.Gen.Nix ( main , horizonGenNix , makeMakePackageSet , makeOverlay ) where import Dhall (auto, inputFile) import Horizon.Gen.Nix.Options (Force, HorizonCommand (MakePackageSetCommand, OverlayCommand), HorizonOptions (MkHorizonOptions), MakePackageSetOptions, OverlayOptions, fromInputFile, horizonGenNixOptsInfo, optForce, optHorizonCommand, optInputFile, optOverlayFile, optPackageSetFile, optPackagesDirectory) import Horizon.Gen.Nix.Types.PackagesDirectory (PackagesDirectory) import Horizon.Gen.Nix.Writers (writeHaskellPackages, writeMakePackageSet, writeOverlay) import Horizon.Spec (Overlay, PackageSet, fromOverlay, packages) import Options.Applicative (execParser) import Path (toFilePath) import Path.Dhall () makeMakePackageSet :: Force -> MakePackageSetOptions -> PackagesDirectory -> PackageSet -> IO () makeMakePackageSet f opts d xs = do writeHaskellPackages d f (packages xs) writeMakePackageSet d (optPackageSetFile opts) xs makeOverlay :: Force -> OverlayOptions -> PackagesDirectory -> Overlay -> IO () makeOverlay f opts d xs = do writeHaskellPackages d f (fromOverlay xs) writeOverlay d (optOverlayFile opts) xs horizonGenNix :: HorizonOptions -> IO () horizonGenNix MkHorizonOptions{..} = let fp = toFilePath . fromInputFile $ optInputFile in case optHorizonCommand of MakePackageSetCommand opts -> do x <- inputFile @PackageSet auto fp makeMakePackageSet optForce opts optPackagesDirectory x OverlayCommand opts -> do x <- inputFile @Overlay auto fp makeOverlay optForce opts optPackagesDirectory x main :: IO () main = do x <- execParser horizonGenNixOptsInfo horizonGenNix x