module Horizon.Gen.Nix.Pretty (prettyDerivation) where import Distribution.Nixpkgs.Haskell.Derivation (Derivation, benchmarkDepends, cabalFlags, configureFlags, dependencies, doBenchmark, doCheck, editedCabalFile, enableExecutableProfiling, enableLibraryProfiling, enableSeparateDataOutput, executableDepends, extraAttributes, extraFunctionArgs, hyperlinkSource, isExecutable, isLibrary, jailbreak, libraryDepends, metaSection, phaseOverrides, pkgid, revision, runHaddock, setupDepends, src, subpath, testDepends, testTarget) import Language.Nix (ident, localName) import Language.Nix.PrettyPrinting (Doc, attr, char, doubleQuotes, empty, funargs, int, lbrace, listattr, nest, onlyIf, pPrint, rbrace, string, text, vcat, ($$), (<+>)) import qualified Language.Nix.PrettyPrinting as P ((<>)) import Control.Lens (each, folded, view, (^.)) import Data.List (isPrefixOf) import qualified Data.Map as Map import Data.Set (Set, toAscList) import qualified Data.Set as Set import Data.Set.Lens (setOf) import Distribution.Nixpkgs.Fetch (derivKind, derivKindFunction, derivUrl) import Distribution.Nixpkgs.Haskell.BuildInfo (pPrintBuildInfo) import Distribution.Nixpkgs.Haskell.OrphanInstances () import Distribution.Nixpkgs.Meta (Meta, broken, description, homepage, license) import Distribution.Package (packageName, packageVersion) import Distribution.PackageDescription (unFlagAssignment, unFlagName) bool :: Bool -> Doc bool True = text "true" bool False = text "false" boolattr :: String -> Bool -> Doc boolattr n v = attr n (bool v) prettyMeta :: Meta -> Doc prettyMeta meta = vcat [ onlyIf (not (null $ meta ^. homepage)) $ attr "homepage" $ string (meta ^. homepage) , onlyIf (not (null $ meta ^. description)) $ attr "description" $ string (meta ^. description) , attr "license" $ pPrint $ meta ^. license , boolattr "broken" (meta ^. broken) ] prettyDerivation :: Derivation -> Doc prettyDerivation drv = funargs (map text ("mkDerivation" : toAscList inputs)) $$ vcat [ text "mkDerivation" <+> lbrace , nest 2 $ vcat [ attr "pname" $ doubleQuotes $ pPrint (packageName $ drv ^. pkgid) , attr "version" $ doubleQuotes $ pPrint (packageVersion $ drv ^. pkgid) , pPrint $ drv ^. src , onlyIf (drv ^. subpath /= ".") $ attr "postUnpack" postUnpack , onlyIf (drv ^. revision > 0) $ attr "revision" $ doubleQuotes $ int $ drv ^. revision , onlyIf (not (null (drv ^. editedCabalFile)) && (drv ^. revision) > 0) $ attr "editedCabalFile" $ string (drv ^. editedCabalFile) , listattr "configureFlags" empty (map (show . show) renderedFlags) , boolattr "isLibrary" $ drv ^. isLibrary , boolattr "isExecutable" $ drv ^. isExecutable , boolattr "enableSeparateDataOutput" $ drv ^. enableSeparateDataOutput , onlyIf (drv ^. setupDepends /= mempty) $ pPrintBuildInfo "setup" $ drv ^. setupDepends , onlyIf (drv ^. libraryDepends /= mempty) $ pPrintBuildInfo "library" $ drv ^. libraryDepends , onlyIf (drv ^. executableDepends /= mempty) $ pPrintBuildInfo "executable" $ drv ^. executableDepends , onlyIf (drv ^. testDepends /= mempty) $ pPrintBuildInfo "test" $ drv ^. testDepends , onlyIf (drv ^. benchmarkDepends /= mempty) $ pPrintBuildInfo "benchmark" $ drv ^. benchmarkDepends , boolattr "enableLibraryProfiling" $ drv ^. enableLibraryProfiling , boolattr "enableExecutableProfiling" $ drv ^. enableExecutableProfiling , boolattr "doHaddock" $ drv ^. runHaddock , boolattr "jailbreak" $ drv ^. jailbreak , boolattr "doCheck" $ drv ^. doCheck , boolattr "doBenchmark" $ drv ^. doBenchmark , onlyIf (not (null $ drv ^. testTarget)) $ attr "testTarget" $ string $ drv ^. testTarget , boolattr "hyperlinkSource" $ drv ^. hyperlinkSource , onlyIf (not (null $ drv ^. phaseOverrides)) $ vcat ((map text . lines) $ drv ^. phaseOverrides) , prettyMeta $ drv ^. metaSection , vcat [ attr k (text v) | (k,v) <- Map.toList $ drv ^. extraAttributes ] ] , rbrace ] where inputs :: Set String inputs = Set.unions [ Set.map (view (localName . ident)) $ drv ^. extraFunctionArgs , setOf (dependencies . each . folded . localName . ident) drv , case derivKind (drv ^. src) of Nothing -> mempty Just derivKind' -> Set.fromList [derivKindFunction derivKind' | not isHackagePackage] ] renderedFlags = [ text "-f" P.<> (if enable then empty else char '-') P.<> text (unFlagName f) | (f, enable) <- unFlagAssignment $ drv ^. cabalFlags ] ++ map text (toAscList (drv ^. configureFlags)) isHackagePackage = "mirror://hackage/" `isPrefixOf` derivUrl (drv ^. src) postUnpack = string $ "sourceRoot+=/" ++ drv ^. subpath ++ "; echo source root reset to $sourceRoot"