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

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


module Main where

import Char
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
    (fields,file,munge,halt) <-
        case args of
          (file:"-slash":fields)
                        -> return (map (map toLower) fields, file, slash, stop)
          (file:"-quiet":"-slash":fields)
                        -> return (map (map toLower) fields, file, slash, quiet)
          (file:"-quiet":fields)
                        -> return (map (map toLower) fields, file, id, quiet)
          (file:fields) -> return (map (map toLower) fields, file, id, stop)
          _ -> stop "Usage: cabal-parse file [-quiet] [-slash] field ..."
    content <- readFile file
    cabal <- case runParser cabalFile (lexToken content) of
               (Left e, _)      -> stop e
               (Right cabal, _) -> return cabal
    let results = flip map fields (\field-> cabalLookup cabal field munge)
    let errs = [ e | Left e <- results ]
    when (not (null errs)) (halt (unlines errs))
    mapM_ putStrLn [ r | Right r <- results ]


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.