module Distribution.InstalledPackageInfo (
InstalledPackageInfo(..),
ParseResult(..), PError(..), PWarning,
emptyInstalledPackageInfo,
parseInstalledPackageInfo,
showInstalledPackageInfo,
showInstalledPackageInfoField,
) where
import Distribution.ParseUtils (
FieldDescr(..), readFields, ParseResult(..), PError(..), PWarning,
Field(F), simpleField, listField, parseLicenseQ,
parseFilePathQ, parseTokenQ, parseModuleNameQ, parsePackageNameQ,
showFilePath, showToken, parseReadS, parseOptVersion, parseQuoted,
showFreeText)
import Distribution.License ( License(..) )
import Distribution.Package ( PackageIdentifier(..), showPackageId,
parsePackageId )
import Distribution.Version ( Version(..), showVersion )
import Distribution.Compat.ReadP as ReadP
import Control.Monad ( foldM )
import Text.PrettyPrint
data InstalledPackageInfo
= InstalledPackageInfo {
package :: PackageIdentifier,
license :: License,
copyright :: String,
maintainer :: String,
author :: String,
stability :: String,
homepage :: String,
pkgUrl :: String,
description :: String,
category :: String,
exposed :: Bool,
exposedModules :: [String],
hiddenModules :: [String],
importDirs :: [FilePath],
libraryDirs :: [FilePath],
hsLibraries :: [String],
extraLibraries :: [String],
extraGHCiLibraries:: [String],
includeDirs :: [FilePath],
includes :: [String],
depends :: [PackageIdentifier],
hugsOptions :: [String],
ccOptions :: [String],
ldOptions :: [String],
frameworkDirs :: [FilePath],
frameworks :: [String],
haddockInterfaces :: [FilePath],
haddockHTMLs :: [FilePath]
}
deriving (Read, Show)
emptyInstalledPackageInfo :: InstalledPackageInfo
emptyInstalledPackageInfo
= InstalledPackageInfo {
package = PackageIdentifier "" noVersion,
license = AllRightsReserved,
copyright = "",
maintainer = "",
author = "",
stability = "",
homepage = "",
pkgUrl = "",
description = "",
category = "",
exposed = False,
exposedModules = [],
hiddenModules = [],
importDirs = [],
libraryDirs = [],
hsLibraries = [],
extraLibraries = [],
extraGHCiLibraries= [],
includeDirs = [],
includes = [],
depends = [],
hugsOptions = [],
ccOptions = [],
ldOptions = [],
frameworkDirs = [],
frameworks = [],
haddockInterfaces = [],
haddockHTMLs = []
}
noVersion :: Version
noVersion = Version{ versionBranch=[], versionTags=[] }
parseInstalledPackageInfo :: String -> ParseResult InstalledPackageInfo
parseInstalledPackageInfo inp = do
stLines <- readFields inp
foldM (parseBasicStanza all_fields) emptyInstalledPackageInfo stLines
parseBasicStanza :: [FieldDescr a]
-> a
-> Field
-> ParseResult a
parseBasicStanza ((FieldDescr name _ set):fields) pkg (F lineNo f val)
| name == f = set lineNo val pkg
| otherwise = parseBasicStanza fields pkg (F lineNo f val)
parseBasicStanza [] pkg _ = return pkg
parseBasicStanza _ _ _ =
error "parseBasicStanza must be called with a simple field."
showInstalledPackageInfo :: InstalledPackageInfo -> String
showInstalledPackageInfo pkg = render (ppFields all_fields)
where
ppFields [] = empty
ppFields ((FieldDescr name get' _):flds) =
pprField name (get' pkg) $$ ppFields flds
showInstalledPackageInfoField
:: String
-> Maybe (InstalledPackageInfo -> String)
showInstalledPackageInfoField field
= case [ (f,get') | (FieldDescr f get' _) <- all_fields, f == field ] of
[] -> Nothing
((f,get'):_) -> Just (render . pprField f . get')
pprField :: String -> Doc -> Doc
pprField name field = text name <> colon <+> field
all_fields :: [FieldDescr InstalledPackageInfo]
all_fields = basicFieldDescrs ++ installedFieldDescrs
basicFieldDescrs :: [FieldDescr InstalledPackageInfo]
basicFieldDescrs =
[ simpleField "name"
text parsePackageNameQ
(pkgName . package) (\name pkg -> pkg{package=(package pkg){pkgName=name}})
, simpleField "version"
(text . showVersion) parseOptVersion
(pkgVersion . package) (\ver pkg -> pkg{package=(package pkg){pkgVersion=ver}})
, simpleField "license"
(text . show) parseLicenseQ
license (\l pkg -> pkg{license=l})
, simpleField "copyright"
showFreeText (munch (const True))
copyright (\val pkg -> pkg{copyright=val})
, simpleField "maintainer"
showFreeText (munch (const True))
maintainer (\val pkg -> pkg{maintainer=val})
, simpleField "stability"
showFreeText (munch (const True))
stability (\val pkg -> pkg{stability=val})
, simpleField "homepage"
showFreeText (munch (const True))
homepage (\val pkg -> pkg{homepage=val})
, simpleField "package-url"
showFreeText (munch (const True))
pkgUrl (\val pkg -> pkg{pkgUrl=val})
, simpleField "description"
showFreeText (munch (const True))
description (\val pkg -> pkg{description=val})
, simpleField "category"
showFreeText (munch (const True))
category (\val pkg -> pkg{category=val})
, simpleField "author"
showFreeText (munch (const True))
author (\val pkg -> pkg{author=val})
]
installedFieldDescrs :: [FieldDescr InstalledPackageInfo]
installedFieldDescrs = [
simpleField "exposed"
(text.show) parseReadS
exposed (\val pkg -> pkg{exposed=val})
, listField "exposed-modules"
text parseModuleNameQ
exposedModules (\xs pkg -> pkg{exposedModules=xs})
, listField "hidden-modules"
text parseModuleNameQ
hiddenModules (\xs pkg -> pkg{hiddenModules=xs})
, listField "import-dirs"
showFilePath parseFilePathQ
importDirs (\xs pkg -> pkg{importDirs=xs})
, listField "library-dirs"
showFilePath parseFilePathQ
libraryDirs (\xs pkg -> pkg{libraryDirs=xs})
, listField "hs-libraries"
showFilePath parseTokenQ
hsLibraries (\xs pkg -> pkg{hsLibraries=xs})
, listField "extra-libraries"
showToken parseTokenQ
extraLibraries (\xs pkg -> pkg{extraLibraries=xs})
, listField "extra-ghci-libraries"
showToken parseTokenQ
extraGHCiLibraries (\xs pkg -> pkg{extraGHCiLibraries=xs})
, listField "include-dirs"
showFilePath parseFilePathQ
includeDirs (\xs pkg -> pkg{includeDirs=xs})
, listField "includes"
showFilePath parseFilePathQ
includes (\xs pkg -> pkg{includes=xs})
, listField "depends"
(text.showPackageId) parsePackageId'
depends (\xs pkg -> pkg{depends=xs})
, listField "hugs-options"
showToken parseTokenQ
hugsOptions (\path pkg -> pkg{hugsOptions=path})
, listField "cc-options"
showToken parseTokenQ
ccOptions (\path pkg -> pkg{ccOptions=path})
, listField "ld-options"
showToken parseTokenQ
ldOptions (\path pkg -> pkg{ldOptions=path})
, listField "framework-dirs"
showFilePath parseFilePathQ
frameworkDirs (\xs pkg -> pkg{frameworkDirs=xs})
, listField "frameworks"
showToken parseTokenQ
frameworks (\xs pkg -> pkg{frameworks=xs})
, listField "haddock-interfaces"
showFilePath parseFilePathQ
haddockInterfaces (\xs pkg -> pkg{haddockInterfaces=xs})
, listField "haddock-html"
showFilePath parseFilePathQ
haddockHTMLs (\xs pkg -> pkg{haddockHTMLs=xs})
]
parsePackageId' :: ReadP [PackageIdentifier] PackageIdentifier
parsePackageId' = parseQuoted parsePackageId <++ parsePackageId