{-# LANGUAGE OverloadedStrings #-} module Horizon.Gen.Nix.Writers ( writeOverlay , writeMakePackageSet , writeCabal2Nix , writeDerivation , writeHaskellPackage , writeHaskellPackages ) where import Cabal2nix (Options, cabal2nix') import Control.Lens ((%~), (&)) import Control.Monad (forM_, unless) import Data.Map (keys, toList) import qualified Data.Text as T import Distribution.Compiler (CompilerId) import Distribution.Nixpkgs.Haskell.Derivation (Derivation, benchmarkDepends, testDepends) import Horizon.Gen.Nix.Cabal2Nix.Options (haskellPackageToCabal2NixOptions) import Horizon.Gen.Nix.Pretty (prettyDerivation) import Horizon.Spec (HaskellPackage, Modifiers, Name (MkName), Overlay (MkOverlay), OverlayFile (MkOverlayFile), PackageList (MkPackageList), PackageSet (MkPackageSet), PackageSetFile (MkPackageSetFile), PackagesDir (MkPackagesDir), fromName, fromPackageList, includeBenchmarks, includeTests, modifiers) import Path (File, Path, parseRelFile, toFilePath, ()) import Path.Dhall () import System.Directory (createDirectoryIfMissing, doesFileExist) import System.IO (IOMode (WriteMode), hPutStrLn, stderr, stdout, withFile) import System.IO.Silently (hSilence) import Text.PrettyPrint.HughesPJClass (render) writeOverlay :: PackagesDir -> OverlayFile -> Overlay -> IO () writeOverlay (MkPackagesDir d) (MkOverlayFile f) (MkOverlay (MkPackageSet _ (MkPackageList xs))) = withFile (toFilePath f) WriteMode $ \h -> do hPutStrLn h "{ pkgs, ... }:" hPutStrLn h "" hPutStrLn h "final: prev: with pkgs.haskell.lib; {" forM_ (keys xs) $ \x -> do y <- parseRelFile $ T.unpack $ fromName x <> ".nix" hPutStrLn h (" " <> T.unpack (fromName x) <> " = final.callPackage (./" <> toFilePath (d y) <> ") { };") hPutStrLn h "" hPutStrLn h "}" writeMakePackageSet :: PackagesDir -> PackageSetFile -> PackageSet -> IO () writeMakePackageSet (MkPackagesDir d) (MkPackageSetFile f) (MkPackageSet _ (MkPackageList xs)) = withFile (toFilePath f) WriteMode $ \h -> do hPutStrLn h "{ pkgs, lib, callPackage, ... }:" hPutStrLn h "" hPutStrLn h "self: with pkgs.haskell.lib; {" forM_ (keys xs) $ \x -> do y <- parseRelFile $ T.unpack $ fromName x <> ".nix" hPutStrLn h (" " <> T.unpack (fromName x) <> " = self.callPackage (./" <> toFilePath (d y) <> ") { };") hPutStrLn h "" hPutStrLn h "}" applyModifiersToDerivation :: Modifiers -> Derivation -> Derivation applyModifiersToDerivation ms drv = drv & testDepends %~ (\x -> if includeTests ms then x else mempty) & benchmarkDepends %~ (\x -> if includeBenchmarks ms then x else mempty) writeCabal2Nix :: Path b File -> Modifiers -> Options -> IO () writeCabal2Nix f ms opts = do putStrLn $ "Fetching " <> toFilePath f x <- hSilence [stdout, stderr] . cabal2nix' $ opts either (print . render) (writeDerivation f . applyModifiersToDerivation ms) x writeDerivation :: Path b File -> Derivation -> IO () writeDerivation f = writeFile (toFilePath f) . show . prettyDerivation writeHaskellPackage :: PackagesDir -> CompilerId -> Name -> HaskellPackage -> IO () writeHaskellPackage (MkPackagesDir d) c (MkName f) y = do let o = haskellPackageToCabal2NixOptions c y createDirectoryIfMissing True (toFilePath d) f' <- parseRelFile $ T.unpack (f <> ".nix") let j = d f' q <- doesFileExist $ toFilePath j unless q $ writeCabal2Nix j (modifiers y) o writeHaskellPackages :: PackagesDir -> CompilerId -> PackageList -> IO () writeHaskellPackages d c = mapM_ (uncurry $ writeHaskellPackage d c) . toList . fromPackageList