Plan 9 from Bell Labs’s /usr/web/sources/contrib/fernan/nhc98/src/libraries/nhc98-pkg.hs

Copyright © 2021 Plan 9 Foundation.
Distributed under the MIT License.
Download the Plan 9 distribution.


module Main where

import List
import Monad
import System
import Text.ParserCombinators.Poly
import CabalParse

-- A simple way of reading information from a .cabal file
-- for use by other external programs, e.g. in a shell script or Makefile.
-- The cmdline arg "-slash" just replaces dots by slashes (e.g. to translate
-- module names from Haskell notation to filepaths).
main = do
    args <- getArgs
    (dir,pkgs,action) <-
        case args of
          (dir:"depends":pkgs)
                        -> return (dir, pkgs, recursiveDeps)
          _ -> stop "Usage: nhc98-pkg <dir> depends <pkg> ..."
    depList <- action dir pkgs
    putStrLn (unwords depList)

-- Given a directory in which to look for cabal files, and a list of starting
-- packages, return a list of all package dependencies in dep order, i.e.
-- top-most in the lattice first.
recursiveDeps :: FilePath -> [String] -> IO [String]
recursiveDeps dir [] = return []
recursiveDeps dir (pkg:pkgs) = do
    deps <- depends dir pkg
    newdeps <- recursiveDeps dir deps
    rest    <- recursiveDeps dir pkgs
    return . minimise . (pkg:) $ newdeps++rest

-- Given a directory in which to look for cabal files, and a package name,
-- return the single-level (direct) dependencies noted in the .cabal file.
depends :: FilePath -> String -> IO [String]
depends dir pkg = do
    content <- readFile (dir++"/"++pkg++".cabal")
    cabal <- case runParser cabalFile (lexToken content) of
               (Left e, _)      -> stop e
               (Right cabal, _) -> return cabal
    let results = map (\field-> cabalLookup cabal field id)
                      ["depends","build-depends"]
    return . nub . words . unwords $ [ r | Right r <- results ]

-- Given a list of values in dependency order, remove duplicates from
-- the list, keeping the more basic items towards the end, i.e. those
-- with greater inward deps, and lesser outward deps.
minimise :: Eq a => [a] -> [a]
minimise = reverse . nub . reverse

Bell Labs OSI certified Powered by Plan 9

(Return to Plan 9 Home Page)

Copyright © 2021 Plan 9 Foundation. All Rights Reserved.
Comments to webmaster@9p.io.