-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.PackageDescription
-- Copyright   :  Isaac Jones 2003-2005
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- This defines the data structure for the @.cabal@ file format. There are
-- several parts to this structure. It has top level info and then 'Library',
-- 'Executable', and 'TestSuite' sections each of which have associated
-- 'BuildInfo' data that's used to build the library, exe, or test. To further
-- complicate things there is both a 'PackageDescription' and a
-- 'GenericPackageDescription'. This distinction relates to cabal
-- configurations. When we initially read a @.cabal@ file we get a
-- 'GenericPackageDescription' which has all the conditional sections.
-- Before actually building a package we have to decide
-- on each conditional. Once we've done that we get a 'PackageDescription'.
-- It was done this way initially to avoid breaking too much stuff when the
-- feature was introduced. It could probably do with being rationalised at some
-- point to make it simpler.

{- All rights reserved.

Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are
met:

    * Redistributions of source code must retain the above copyright
      notice, this list of conditions and the following disclaimer.

    * Redistributions in binary form must reproduce the above
      copyright notice, this list of conditions and the following
      disclaimer in the documentation and/or other materials provided
      with the distribution.

    * Neither the name of Isaac Jones nor the names of other
      contributors may be used to endorse or promote products derived
      from this software without specific prior written permission.

THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}

module Distribution.PackageDescription (
        -- * Package descriptions
        PackageDescription(..),
        emptyPackageDescription,
        specVersion,
        descCabalVersion,
        BuildType(..),
        knownBuildTypes,

        -- ** Primary Components
        Component(..),
        compSel,

        -- ** Libraries
        Library(..),
        emptyLibrary,
        withLib,
        hasLibs,
        libModules,

        -- ** Executables
        Executable(..),
        emptyExecutable,
        withExe,
        hasExes,
        exeModules,

        -- * Tests
        TestSuite(..),
        TestSuiteInterface(..),
        TestType(..),
        testType,
        knownTestTypes,
        emptyTestSuite,
        hasTests,
        withTest,
        testModules,
        enabledTests,

        -- * Build information
        BuildInfo(..),
        emptyBuildInfo,
        allBuildInfo,
        allComponentsBy,
        allLanguages,
        allExtensions,
        usedExtensions,
        hcOptions,

        -- ** Supplementary build information
        HookedBuildInfo,
        emptyHookedBuildInfo,
        updatePackageDescription,

        -- * package configuration
        GenericPackageDescription(..),
        Flag(..), FlagName(..), FlagAssignment,
        CondTree(..), ConfVar(..), Condition(..),

        -- * Source repositories
        SourceRepo(..),
        RepoKind(..),
        RepoType(..),
        knownRepoTypes,
  ) where

import Data.List   (nub, intersperse)
import Data.Maybe  (maybeToList)
import Data.Monoid (Monoid(mempty, mappend))
import Control.Monad (MonadPlus(mplus))
import Text.PrettyPrint.HughesPJ as Disp
import qualified Distribution.Compat.ReadP as Parse
import qualified Data.Char as Char (isAlphaNum, isDigit, toLower)

import Distribution.Package
         ( PackageName(PackageName), PackageIdentifier(PackageIdentifier)
         , Dependency, Package(..) )
import Distribution.ModuleName ( ModuleName )
import Distribution.Version
         ( Version(Version), VersionRange, anyVersion, orLaterVersion
         , asVersionIntervals, LowerBound(..) )
import Distribution.License  (License(AllRightsReserved))
import Distribution.Compiler (CompilerFlavor)
import Distribution.System   (OS, Arch)
import Distribution.Text
         ( Text(..), display )
import Language.Haskell.Extension
         ( Language, Extension )

-- -----------------------------------------------------------------------------
-- The PackageDescription type

-- | This data type is the internal representation of the file @pkg.cabal@.
-- It contains two kinds of information about the package: information
-- which is needed for all packages, such as the package name and version, and
-- information which is needed for the simple build system only, such as
-- the compiler options and library name.
--
data testedWith :: [(CompilerFlavor, VersionRange)]PackageDescription
    =  PackageDescription {
        -- the following are required by all packages:
        package        :: PackageIdentifier,
        license        :: License,
        licenseFile    :: FilePath,
        copyright      :: String,
        maintainer     :: String,
        author         :: String,
        stability      :: String,
        testedWith     :: [(CompilerFlavor,VersionRange)],
        homepage       :: String,
        pkgUrl         :: String,
        bugReports     :: String,
        sourceRepos    :: [SourceRepo],
        synopsis       :: String, -- ^A one-line summary of this package
        description    :: String, -- ^A more verbose description of this package
        category       :: String,
        customFieldsPD :: [(String,String)], -- ^Custom fields starting
                                             -- with x-, stored in a
                                             -- simple assoc-list.
        buildDepends   :: [Dependency],
        -- | The version of the Cabal spec that this package description uses.
        -- For historical reasons this is specified with a version range but
        -- only ranges of the form @>= v@ make sense. We are in the process of
        -- transitioning to specifying just a single version, not a range.
        specVersionRaw :: Either Version VersionRange,
        buildType      :: Maybe BuildType,
        -- components
        library        :: Maybe Library,
        executables    :: [Executable],
        testSuites     :: [TestSuite],
        dataFiles      :: [FilePath],
        dataDir        :: FilePath,
        extraSrcFiles  :: [FilePath],
        extraTmpFiles  :: [FilePath]
    }
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

instance D:Package :: (pkg -> PackageIdentifier) -> T:Package pkgPackage PackageDescription where
  packageId = package :: PackageDescription -> PackageIdentifierpackage

-- | The version of the Cabal spec that this package should be interpreted
-- against.
--
-- Historically we used a version range but we are switching to using a single
-- version. Currently we accept either. This function converts into a single
-- version by ignoring upper bounds in the version range.
--
specVersion :: PackageDescription -> Version
specVersion pkg = case specVersionRaw :: PackageDescription -> Either Version VersionRangespecVersionRaw pkg :: PackageDescriptionpkg of
  Left  version      -> version :: Versionversion
  Right versionRange -> case asVersionIntervals :: VersionRange -> [VersionInterval]asVersionIntervals versionRange :: VersionRangeversionRange of
                          []                            -> Version :: [Int] -> [String] -> VersionVersion [0] [] :: [a][]
                          ((LowerBound version _, _):_) -> version :: Versionversion

-- | The range of versions of the Cabal tools that this package is intended to
-- work with.
--
-- This function is deprecated and should not be used for new purposes, only to
-- support old packages that rely on the old interpretation.
--
descCabalVersion :: PackageDescription -> VersionRange
descCabalVersion pkg = case specVersionRaw :: PackageDescription -> Either Version VersionRangespecVersionRaw pkg :: PackageDescriptionpkg of
  Left  version      -> orLaterVersion :: Version -> VersionRangeorLaterVersion version :: Versionversion
  Right versionRange -> versionRange :: VersionRangeversionRange
{-# DEPRECATED descCabalVersion "Use specVersion instead" #-}

emptyPackageDescription :: PackageDescription
emptyPackageDescription
    =  PackageDescription {
                      package      = PackageIdentifier :: PackageName -> Version -> PackageIdentifierPackageIdentifier (PackageName :: String -> PackageNamePackageName "")
                                                       (Version :: [Int] -> [String] -> VersionVersion [] :: [a][] [] :: [a][]),
                      license      = AllRightsReserved :: LicenseAllRightsReserved,
                      licenseFile  = "",
                      specVersionRaw = Right :: b -> Either a bRight anyVersion :: VersionRangeanyVersion,
                      buildType    = Nothing :: Maybe aNothing,
                      copyright    = "",
                      maintainer   = "",
                      author       = "",
                      stability    = "",
                      testedWith   = [] :: [a][],
                      buildDepends = [] :: [a][],
                      homepage     = "",
                      pkgUrl       = "",
                      bugReports   = "",
                      sourceRepos  = [] :: [a][],
                      synopsis     = "",
                      description  = "",
                      category     = "",
                      customFieldsPD = [] :: [a][],
                      library      = Nothing :: Maybe aNothing,
                      executables  = [] :: [a][],
                      testSuites   = [] :: [a][],
                      dataFiles    = [] :: [a][],
                      dataDir      = "",
                      extraSrcFiles = [] :: [a][],
                      extraTmpFiles = [] :: [a][]
                     }

-- | The type of build system used by this package.
data BuildType
  = Simple      -- ^ calls @Distribution.Simple.defaultMain@
  | Configure   -- ^ calls @Distribution.Simple.defaultMainWithHooks defaultUserHooks@,
                -- which invokes @configure@ to generate additional build
                -- information used by later phases.
  | Make        -- ^ calls @Distribution.Make.defaultMain@
  | Custom      -- ^ uses user-supplied @Setup.hs@ or @Setup.lhs@ (default)
  | UnknownBuildType String
                -- ^ a package that uses an unknown build type cannot actually
                --   be built. Doing it this way rather than just giving a
                --   parse error means we get better error messages and allows
                --   you to inspect the rest of the package description.
                deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

knownBuildTypes :: [BuildType]
knownBuildTypes = [Simple :: BuildTypeSimple, Configure :: BuildTypeConfigure, Make :: BuildTypeMake, Custom :: BuildTypeCustom]

instance D:Text :: (a -> Doc) -> (forall r. ReadP r a) -> T:Text aText BuildType where
  disp (UnknownBuildType other) = text :: String -> DocDisp.text other :: BuildTypeother
  disp other                    = text :: String -> DocDisp.text (show :: Show a => a -> Stringshow other :: BuildTypeother)

  parse = do
    name <- munch1 :: (Char -> Bool) -> ReadP r StringParse.munch1 isAlphaNum :: Char -> BoolChar.isAlphaNum
    return :: Monad m => forall a. a -> m areturn ($) :: (a -> b) -> a -> b$ case name :: Stringname of
      "Simple"    -> Simple :: BuildTypeSimple
      "Configure" -> Configure :: BuildTypeConfigure
      "Custom"    -> Custom :: BuildTypeCustom
      "Make"      -> Make :: BuildTypeMake
      _           -> UnknownBuildType :: String -> BuildTypeUnknownBuildType name :: Stringname

-- ---------------------------------------------------------------------------
-- The Library type

data exposedModules :: [ModuleName]Library = Library {
        exposedModules    :: [ModuleName],
        libExposed        :: Bool, -- ^ Is the lib to be exposed by default?
        libBuildInfo      :: BuildInfo
    }
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead)

instance D:Monoid :: a -> (a -> a -> a) -> ([a] -> a) -> T:Monoid aMonoid Library where
  mempty = Library {
    exposedModules = mempty :: Monoid a => amempty,
    libExposed     = True :: BoolTrue,
    libBuildInfo   = mempty :: Monoid a => amempty
  }
  mappend a b = Library {
    exposedModules = combine :: (Library -> a) -> acombine exposedModules :: Library -> [ModuleName]exposedModules,
    libExposed     = libExposed :: Library -> BoollibExposed a :: Librarya (&&) :: Bool -> Bool -> Bool&& libExposed :: Library -> BoollibExposed b :: Libraryb, -- so False propagates
    libBuildInfo   = combine :: (Library -> a) -> acombine libBuildInfo :: Library -> BuildInfolibBuildInfo
  }
    where combine field = field :: Library -> afield a :: Librarya mappend :: Monoid a => a -> a -> a`mappend` field :: Library -> afield b :: Libraryb

emptyLibrary :: Library
emptyLibrary = mempty :: Monoid a => amempty

-- |does this package have any libraries?
hasLibs :: PackageDescription -> Bool
hasLibs p = maybe :: b -> (a -> b) -> Maybe a -> bmaybe False :: BoolFalse (buildable :: BuildInfo -> Boolbuildable (.) :: (b -> c) -> (a -> b) -> a -> c. libBuildInfo :: Library -> BuildInfolibBuildInfo) (library :: PackageDescription -> Maybe Librarylibrary p :: PackageDescriptionp)

-- |'Maybe' version of 'hasLibs'
maybeHasLibs :: PackageDescription -> Maybe Library
maybeHasLibs p =
   library :: PackageDescription -> Maybe Librarylibrary p :: PackageDescriptionp (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= \lib -> if buildable :: BuildInfo -> Boolbuildable (libBuildInfo :: Library -> BuildInfolibBuildInfo lib :: Librarylib)
                           then Just :: a -> Maybe aJust lib :: Librarylib
                           else Nothing :: Maybe aNothing

-- |If the package description has a library section, call the given
--  function with the library build info as argument.
withLib :: PackageDescription -> (Library -> IO ()) -> IO ()
withLib pkg_descr f =
   maybe :: b -> (a -> b) -> Maybe a -> bmaybe (return :: Monad m => forall a. a -> m areturn ()) f :: TestSuite -> [Char]f (maybeHasLibs :: PackageDescription -> Maybe LibrarymaybeHasLibs pkg_descr :: PackageDescriptionpkg_descr)

-- | Get all the module names from the library (exposed and internal modules)
libModules :: Library -> [ModuleName]
libModules lib = exposedModules :: Library -> [ModuleName]exposedModules lib :: Librarylib
              (++) :: [a] -> [a] -> [a]++ otherModules :: BuildInfo -> [ModuleName]otherModules (libBuildInfo :: Library -> BuildInfolibBuildInfo lib :: Librarylib)

-- ---------------------------------------------------------------------------
-- The Executable type

data modulePath :: FilePathExecutable = Executable {
        exeName    :: String,
        modulePath :: FilePath,
        buildInfo  :: BuildInfo
    }
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

instance D:Monoid :: a -> (a -> a -> a) -> ([a] -> a) -> T:Monoid aMonoid Executable where
  mempty = Executable {
    exeName    = mempty :: Monoid a => amempty,
    modulePath = mempty :: Monoid a => amempty,
    buildInfo  = mempty :: Monoid a => amempty
  }
  mappend a b = Executable{
    exeName    = combine' :: (Executable -> [Char]) -> [Char]combine' exeName :: Executable -> StringexeName,
    modulePath = combine :: (Library -> a) -> acombine modulePath :: Executable -> FilePathmodulePath,
    buildInfo  = combine :: (Library -> a) -> acombine buildInfo :: Executable -> BuildInfobuildInfo
  }
    where combine field = field :: Library -> afield a :: Librarya mappend :: Monoid a => a -> a -> a`mappend` field :: Library -> afield b :: Libraryb
          combine' field = case (field :: Library -> afield a :: Librarya, field :: Library -> afield b :: Libraryb) of
                      ("","") -> ""
                      ("", x) -> x :: [Char]x
                      (x, "") -> x :: [Char]x
                      (x, y) -> error :: [Char] -> aerror ($) :: (a -> b) -> a -> b$ "Ambiguous values for executable field: '"
                                  (++) :: [a] -> [a] -> [a]++ x :: [Char]x (++) :: [a] -> [a] -> [a]++ "' and '" (++) :: [a] -> [a] -> [a]++ y :: [Char]y (++) :: [a] -> [a] -> [a]++ "'"

emptyExecutable :: Executable
emptyExecutable = mempty :: Monoid a => amempty

-- |does this package have any executables?
hasExes :: PackageDescription -> Bool
hasExes p = any :: (a -> Bool) -> [a] -> Boolany (buildable :: BuildInfo -> Boolbuildable (.) :: (b -> c) -> (a -> b) -> a -> c. buildInfo :: Executable -> BuildInfobuildInfo) (executables :: PackageDescription -> [Executable]executables p :: PackageDescriptionp)

-- | Perform the action on each buildable 'Executable' in the package
-- description.
withExe :: PackageDescription -> (Executable -> IO ()) -> IO ()
withExe pkg_descr f =
  sequence_ :: Monad m => [m a] -> m ()sequence_ [f :: TestSuite -> [Char]f exe :: Executableexe | exe <- executables :: PackageDescription -> [Executable]executables pkg_descr :: PackageDescriptionpkg_descr, buildable :: BuildInfo -> Boolbuildable (buildInfo :: Executable -> BuildInfobuildInfo exe :: Executableexe)]

-- | Get all the module names from an exe
exeModules :: Executable -> [ModuleName]
exeModules exe = otherModules :: BuildInfo -> [ModuleName]otherModules (buildInfo :: Executable -> BuildInfobuildInfo exe :: Executableexe)

-- ---------------------------------------------------------------------------
-- The TestSuite type

-- | A \"test-suite\" stanza in a cabal file.
--
data testInterface :: TestSuiteInterfaceTestSuite = TestSuite {
        testName      :: String,
        testInterface :: TestSuiteInterface,
        testBuildInfo :: BuildInfo,
        testEnabled   :: Bool
        -- TODO: By having a 'testEnabled' field in the PackageDescription, we
        -- are mixing build status information (i.e., arguments to 'configure')
        -- with static package description information. This is undesirable, but
        -- a better solution is waiting on the next overhaul to the
        -- GenericPackageDescription -> PackageDescription resolution process.
    }
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

-- | The test suite interfaces that are currently defined. Each test suite must
-- specify which interface it supports.
--
-- More interfaces may be defined in future, either new revisions or totally
-- new interfaces.
--
data TestSuiteInterface =

     -- | Test interface \"exitcode-stdio-1.0\". The test-suite takes the form
     -- of an executable. It returns a zero exit code for success, non-zero for
     -- failure. The stdout and stderr channels may be logged. It takes no
     -- command line parameters and nothing on stdin.
     --
     TestSuiteExeV10 Version FilePath

     -- | Test interface \"detailed-0.9\". The test-suite takes the form of a
     -- library containing a designated module that exports \"tests :: [Test]\".
     --
   | TestSuiteLibV09 Version ModuleName

     -- | A test suite that does not conform to one of the above interfaces for
     -- the given reason (e.g. unknown test type).
     --
   | TestSuiteUnsupported TestType
   deriving (($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow)

instance D:Monoid :: a -> (a -> a -> a) -> ([a] -> a) -> T:Monoid aMonoid TestSuite where
    mempty = TestSuite {
        testName      = mempty :: Monoid a => amempty,
        testInterface = mempty :: Monoid a => amempty,
        testBuildInfo = mempty :: Monoid a => amempty,
        testEnabled   = False :: BoolFalse
    }

    mappend a b = TestSuite {
        testName      = combine' :: (Executable -> [Char]) -> [Char]combine' testName :: TestSuite -> StringtestName,
        testInterface = combine :: (Library -> a) -> acombine  testInterface :: TestSuite -> TestSuiteInterfacetestInterface,
        testBuildInfo = combine :: (Library -> a) -> acombine  testBuildInfo :: TestSuite -> BuildInfotestBuildInfo,
        testEnabled   = if testEnabled :: TestSuite -> BooltestEnabled a :: Librarya then True :: BoolTrue else testEnabled :: TestSuite -> BooltestEnabled b :: Libraryb
    }
        where combine   field = field :: Library -> afield a :: Librarya mappend :: Monoid a => a -> a -> a`mappend` field :: Library -> afield b :: Libraryb
              combine' f = case (f :: TestSuite -> [Char]f a :: Librarya, f :: TestSuite -> [Char]f b :: Libraryb) of
                        ("", x) -> x :: [Char]x
                        (x, "") -> x :: [Char]x
                        (x, y) -> error :: [Char] -> aerror "Ambiguous values for test field: '"
                            (++) :: [a] -> [a] -> [a]++ x :: [Char]x (++) :: [a] -> [a] -> [a]++ "' and '" (++) :: [a] -> [a] -> [a]++ y :: [Char]y (++) :: [a] -> [a] -> [a]++ "'"

instance D:Monoid :: a -> (a -> a -> a) -> ([a] -> a) -> T:Monoid aMonoid TestSuiteInterface where
    mempty  =  TestSuiteUnsupported :: TestType -> TestSuiteInterfaceTestSuiteUnsupported (TestTypeUnknown :: String -> Version -> TestTypeTestTypeUnknown mempty :: Monoid a => amempty (Version :: [Int] -> [String] -> VersionVersion [] :: [a][] [] :: [a][]))
    mappend a (TestSuiteUnsupported _) = a :: Librarya
    mappend _ b                        = b :: Libraryb

emptyTestSuite :: TestSuite
emptyTestSuite = mempty :: Monoid a => amempty

-- | Does this package have any test suites?
hasTests :: PackageDescription -> Bool
hasTests = any :: (a -> Bool) -> [a] -> Boolany (buildable :: BuildInfo -> Boolbuildable (.) :: (b -> c) -> (a -> b) -> a -> c. testBuildInfo :: TestSuite -> BuildInfotestBuildInfo) (.) :: (b -> c) -> (a -> b) -> a -> c. testSuites :: PackageDescription -> [TestSuite]testSuites

-- | Get all the enabled test suites from a package.
enabledTests :: PackageDescription -> [TestSuite]
enabledTests = filter :: (a -> Bool) -> [a] -> [a]filter testEnabled :: TestSuite -> BooltestEnabled (.) :: (b -> c) -> (a -> b) -> a -> c. testSuites :: PackageDescription -> [TestSuite]testSuites

-- | Perform an action on each buildable 'TestSuite' in a package.
withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO ()
withTest pkg_descr f =
    mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ f :: TestSuite -> [Char]f ($) :: (a -> b) -> a -> b$ filter :: (a -> Bool) -> [a] -> [a]filter (buildable :: BuildInfo -> Boolbuildable (.) :: (b -> c) -> (a -> b) -> a -> c. testBuildInfo :: TestSuite -> BuildInfotestBuildInfo) ($) :: (a -> b) -> a -> b$ enabledTests :: PackageDescription -> [TestSuite]enabledTests pkg_descr :: PackageDescriptionpkg_descr

-- | Get all the module names from a test suite.
testModules :: TestSuite -> [ModuleName]
testModules test = (case testInterface :: TestSuite -> TestSuiteInterfacetestInterface test :: TestSuitetest of
                     TestSuiteLibV09 _ m -> [m :: ModuleNamem]
                     _                   -> [] :: [a][])
                (++) :: [a] -> [a] -> [a]++ otherModules :: BuildInfo -> [ModuleName]otherModules (testBuildInfo :: TestSuite -> BuildInfotestBuildInfo test :: TestSuitetest)

-- | The \"test-type\" field in the test suite stanza.
--
data TestType = TestTypeExe Version     -- ^ \"type: exitcode-stdio-x.y\"
              | TestTypeLib Version     -- ^ \"type: detailed-x.y\"
              | TestTypeUnknown String Version -- ^ Some unknown test type e.g. \"type: foo\"
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

knownTestTypes :: [TestType]
knownTestTypes = [ TestTypeExe :: Version -> TestTypeTestTypeExe (Version :: [Int] -> [String] -> VersionVersion [1,0] [] :: [a][])
                 , TestTypeLib :: Version -> TestTypeTestTypeLib (Version :: [Int] -> [String] -> VersionVersion [0,9] [] :: [a][]) ]

instance D:Text :: (a -> Doc) -> (forall r. ReadP r a) -> T:Text aText TestType where
  disp (TestTypeExe ver)          = text :: String -> Doctext "exitcode-stdio-" (<>) :: Doc -> Doc -> Doc<> disp :: Text a => a -> Docdisp ver :: Versionver
  disp (TestTypeLib ver)          = text :: String -> Doctext "detailed-"       (<>) :: Doc -> Doc -> Doc<> disp :: Text a => a -> Docdisp ver :: Versionver
  disp (TestTypeUnknown name ver) = text :: String -> Doctext name :: Stringname (<>) :: Doc -> Doc -> Doc<> char :: Char -> Docchar '-' (<>) :: Doc -> Doc -> Doc<> disp :: Text a => a -> Docdisp ver :: Versionver

  parse = do
    cs   <- sepBy1 :: ReadP r a -> ReadP r sep -> ReadP r [a]Parse.sepBy1 component :: Parser r Char Stringcomponent (char :: Char -> ReadP r CharParse.char '-')
    _    <- char :: Char -> ReadP r CharParse.char '-'
    ver  <- parse :: Text a => forall r. ReadP r aparse
    let name = concat :: [[a]] -> [a]concat (intersperse :: a -> [a] -> [a]intersperse "-" cs :: Stringcs)
    return :: Monad m => forall a. a -> m areturn ($!) :: (a -> b) -> a -> b$! case lowercase :: String -> Stringlowercase name :: Stringname of
      "exitcode-stdio" -> TestTypeExe :: Version -> TestTypeTestTypeExe ver :: Versionver
      "detailed"       -> TestTypeLib :: Version -> TestTypeTestTypeLib ver :: Versionver
      _                -> TestTypeUnknown :: String -> Version -> TestTypeTestTypeUnknown name :: Stringname ver :: Versionver

    where
      component = do
        cs <- munch1 :: (Char -> Bool) -> ReadP r StringParse.munch1 isAlphaNum :: Char -> BoolChar.isAlphaNum
        if all :: (a -> Bool) -> [a] -> Boolall isDigit :: Char -> BoolChar.isDigit cs :: Stringcs then pfail :: ReadP r aParse.pfail else return :: Monad m => forall a. a -> m areturn cs :: Stringcs
        -- each component must contain an alphabetic character, to avoid
        -- ambiguity in identifiers like foo-1 (the 1 is the version number).

testType :: TestSuite -> TestType
testType test = case testInterface :: TestSuite -> TestSuiteInterfacetestInterface test :: TestSuitetest of
  TestSuiteExeV10 ver _         -> TestTypeExe :: Version -> TestTypeTestTypeExe ver :: Versionver
  TestSuiteLibV09 ver _         -> TestTypeLib :: Version -> TestTypeTestTypeLib ver :: Versionver
  TestSuiteUnsupported testtype -> testtype :: TestTypetesttype

-- ---------------------------------------------------------------------------
-- The BuildInfo type

-- Consider refactoring into executable and library versions.
data options :: [(CompilerFlavor, [String])]BuildInfo = BuildInfo {
        buildable         :: Bool,      -- ^ component is buildable here
        buildTools        :: [Dependency], -- ^ tools needed to build this bit
        cppOptions        :: [String],  -- ^ options for pre-processing Haskell code
        ccOptions         :: [String],  -- ^ options for C compiler
        ldOptions         :: [String],  -- ^ options for linker
        pkgconfigDepends  :: [Dependency], -- ^ pkg-config packages that are used
        frameworks        :: [String], -- ^support frameworks for Mac OS X
        cSources          :: [FilePath],
        hsSourceDirs      :: [FilePath], -- ^ where to look for the haskell module hierarchy
        otherModules      :: [ModuleName], -- ^ non-exposed or non-main modules

        defaultLanguage   :: Maybe Language,-- ^ language used when not explicitly specified
        otherLanguages    :: [Language],    -- ^ other languages used within the package
        defaultExtensions :: [Extension],   -- ^ language extensions used by all modules
        otherExtensions   :: [Extension],   -- ^ other language extensions used within the package
        oldExtensions     :: [Extension],   -- ^ the old extensions field, treated same as 'defaultExtensions'

        extraLibs         :: [String], -- ^ what libraries to link with when compiling a program that uses your package
        extraLibDirs      :: [String],
        includeDirs       :: [FilePath], -- ^directories to find .h files
        includes          :: [FilePath], -- ^ The .h files to be found in includeDirs
        installIncludes   :: [FilePath], -- ^ .h files to install with the package
        options           :: [(CompilerFlavor,[String])],
        ghcProfOptions    :: [String],
        ghcSharedOptions  :: [String],
        customFieldsBI    :: [(String,String)], -- ^Custom fields starting
                                                -- with x-, stored in a
                                                -- simple assoc-list.
        targetBuildDepends :: [Dependency] -- ^ Dependencies specific to a library or executable target
    }
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow,D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead,($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

instance D:Monoid :: a -> (a -> a -> a) -> ([a] -> a) -> T:Monoid aMonoid BuildInfo where
  mempty = BuildInfo {
    buildable         = True :: BoolTrue,
    buildTools        = [] :: [a][],
    cppOptions        = [] :: [a][],
    ccOptions         = [] :: [a][],
    ldOptions         = [] :: [a][],
    pkgconfigDepends  = [] :: [a][],
    frameworks        = [] :: [a][],
    cSources          = [] :: [a][],
    hsSourceDirs      = [] :: [a][],
    otherModules      = [] :: [a][],
    defaultLanguage   = Nothing :: Maybe aNothing,
    otherLanguages    = [] :: [a][],
    defaultExtensions = [] :: [a][],
    otherExtensions   = [] :: [a][],
    oldExtensions     = [] :: [a][],
    extraLibs         = [] :: [a][],
    extraLibDirs      = [] :: [a][],
    includeDirs       = [] :: [a][],
    includes          = [] :: [a][],
    installIncludes   = [] :: [a][],
    options           = [] :: [a][],
    ghcProfOptions    = [] :: [a][],
    ghcSharedOptions  = [] :: [a][],
    customFieldsBI    = [] :: [a][],
    targetBuildDepends = [] :: [a][]
  }
  mappend a b = BuildInfo {
    buildable         = buildable :: BuildInfo -> Boolbuildable a :: Librarya (&&) :: Bool -> Bool -> Bool&& buildable :: BuildInfo -> Boolbuildable b :: Libraryb,
    buildTools        = combine :: (Library -> a) -> acombine    buildTools :: BuildInfo -> [Dependency]buildTools,
    cppOptions        = combine :: (Library -> a) -> acombine    cppOptions :: BuildInfo -> [String]cppOptions,
    ccOptions         = combine :: (Library -> a) -> acombine    ccOptions :: BuildInfo -> [String]ccOptions,
    ldOptions         = combine :: (Library -> a) -> acombine    ldOptions :: BuildInfo -> [String]ldOptions,
    pkgconfigDepends  = combine :: (Library -> a) -> acombine    pkgconfigDepends :: BuildInfo -> [Dependency]pkgconfigDepends,
    frameworks        = combineNub :: (BuildInfo -> [a]) -> [a]combineNub frameworks :: BuildInfo -> [String]frameworks,
    cSources          = combineNub :: (BuildInfo -> [a]) -> [a]combineNub cSources :: BuildInfo -> [FilePath]cSources,
    hsSourceDirs      = combineNub :: (BuildInfo -> [a]) -> [a]combineNub hsSourceDirs :: BuildInfo -> [FilePath]hsSourceDirs,
    otherModules      = combineNub :: (BuildInfo -> [a]) -> [a]combineNub otherModules :: BuildInfo -> [ModuleName]otherModules,
    defaultLanguage   = combineMby :: (BuildInfo -> m a) -> m acombineMby defaultLanguage :: BuildInfo -> Maybe LanguagedefaultLanguage,
    otherLanguages    = combineNub :: (BuildInfo -> [a]) -> [a]combineNub otherLanguages :: BuildInfo -> [Language]otherLanguages,
    defaultExtensions = combineNub :: (BuildInfo -> [a]) -> [a]combineNub defaultExtensions :: BuildInfo -> [Extension]defaultExtensions,
    otherExtensions   = combineNub :: (BuildInfo -> [a]) -> [a]combineNub otherExtensions :: BuildInfo -> [Extension]otherExtensions,
    oldExtensions     = combineNub :: (BuildInfo -> [a]) -> [a]combineNub oldExtensions :: BuildInfo -> [Extension]oldExtensions,
    extraLibs         = combine :: (Library -> a) -> acombine    extraLibs :: BuildInfo -> [String]extraLibs,
    extraLibDirs      = combineNub :: (BuildInfo -> [a]) -> [a]combineNub extraLibDirs :: BuildInfo -> [String]extraLibDirs,
    includeDirs       = combineNub :: (BuildInfo -> [a]) -> [a]combineNub includeDirs :: BuildInfo -> [FilePath]includeDirs,
    includes          = combineNub :: (BuildInfo -> [a]) -> [a]combineNub includes :: BuildInfo -> [FilePath]includes,
    installIncludes   = combineNub :: (BuildInfo -> [a]) -> [a]combineNub installIncludes :: BuildInfo -> [FilePath]installIncludes,
    options           = combine :: (Library -> a) -> acombine    options :: BuildInfo -> [(CompilerFlavor, [String])]options,
    ghcProfOptions    = combine :: (Library -> a) -> acombine    ghcProfOptions :: BuildInfo -> [String]ghcProfOptions,
    ghcSharedOptions  = combine :: (Library -> a) -> acombine    ghcSharedOptions :: BuildInfo -> [String]ghcSharedOptions,
    customFieldsBI    = combine :: (Library -> a) -> acombine    customFieldsBI :: BuildInfo -> [(String, String)]customFieldsBI,
    targetBuildDepends = combineNub :: (BuildInfo -> [a]) -> [a]combineNub targetBuildDepends :: BuildInfo -> [Dependency]targetBuildDepends
  }
    where
      combine    field = field :: Library -> afield a :: Librarya mappend :: Monoid a => a -> a -> a`mappend` field :: Library -> afield b :: Libraryb
      combineNub field = nub :: Eq a => [a] -> [a]nub (combine :: (Library -> a) -> acombine field :: Library -> afield)
      combineMby field = field :: Library -> afield b :: Libraryb mplus :: MonadPlus m => forall a. m a -> m a -> m a`mplus` field :: Library -> afield a :: Librarya

emptyBuildInfo :: BuildInfo
emptyBuildInfo = mempty :: Monoid a => amempty

-- | The 'BuildInfo' for the library (if there is one and it's buildable), and
-- all buildable executables and test suites.  Useful for gathering dependencies.
allBuildInfo :: PackageDescription -> [BuildInfo]
allBuildInfo = flip :: (a -> b -> c) -> b -> a -> cflip allComponentsBy :: PackageDescription -> (Component -> a) -> [a]allComponentsBy
             ($) :: (a -> b) -> a -> b$ compSel ::
  (Library -> a)
  -> (Executable -> a)
  -> (TestSuite -> a)
  -> Component
  -> acompSel libBuildInfo :: Library -> BuildInfolibBuildInfo buildInfo :: Executable -> BuildInfobuildInfo testBuildInfo :: TestSuite -> BuildInfotestBuildInfo
  --FIXME: many of the places where this is used, we actually want to look at
  --       unbuildable bits too, probably need separate functions

data Component = CLib Library
               | CExe Executable
               | CTst TestSuite
               deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead)

compSel :: (Library -> a)
        -> (Executable -> a)
        -> (TestSuite -> a)
        -> Component
        -> a
compSel f _ _ (CLib l) = f :: TestSuite -> [Char]f l :: Libraryl
compSel _ f _ (CExe e) = f :: TestSuite -> [Char]f e :: Executablee
compSel _ _ f (CTst t) = f :: TestSuite -> [Char]f t :: TestSuitet

-- | Obtains all components (libs, exes, or test suites), transformed by the
-- given function.  Useful for gathering dependencies with component context.
allComponentsBy :: PackageDescription
                -> (Component -> a)
                -> [a]
allComponentsBy pkg_descr f = [ f :: TestSuite -> [Char]f (CLib :: Library -> ComponentCLib l :: Libraryl) | Just l <- [library :: PackageDescription -> Maybe Librarylibrary pkg_descr :: PackageDescriptionpkg_descr]
                                           , buildable :: BuildInfo -> Boolbuildable (libBuildInfo :: Library -> BuildInfolibBuildInfo l :: Libraryl)
                              ]
                              (++) :: [a] -> [a] -> [a]++
                              [ f :: TestSuite -> [Char]f (CExe :: Executable -> ComponentCExe e :: Executablee) | e <- executables :: PackageDescription -> [Executable]executables pkg_descr :: PackageDescriptionpkg_descr
                                           , buildable :: BuildInfo -> Boolbuildable (buildInfo :: Executable -> BuildInfobuildInfo e :: Executablee)
                              ]
                              (++) :: [a] -> [a] -> [a]++
                              [ f :: TestSuite -> [Char]f (CTst :: TestSuite -> ComponentCTst t :: TestSuitet) | t <- testSuites :: PackageDescription -> [TestSuite]testSuites pkg_descr :: PackageDescriptionpkg_descr
                                           , buildable :: BuildInfo -> Boolbuildable (testBuildInfo :: TestSuite -> BuildInfotestBuildInfo t :: TestSuitet)
                                           , testEnabled :: TestSuite -> BooltestEnabled t :: TestSuitet
                              ]

-- | The 'Language's used by this component
--
allLanguages :: BuildInfo -> [Language]
allLanguages bi = maybeToList :: Maybe a -> [a]maybeToList (defaultLanguage :: BuildInfo -> Maybe LanguagedefaultLanguage bi :: BuildInfobi)
               (++) :: [a] -> [a] -> [a]++ otherLanguages :: BuildInfo -> [Language]otherLanguages bi :: BuildInfobi

-- | The 'Extension's that are used somewhere by this component
--
allExtensions :: BuildInfo -> [Extension]
allExtensions bi = usedExtensions :: BuildInfo -> [Extension]usedExtensions bi :: BuildInfobi
                (++) :: [a] -> [a] -> [a]++ otherExtensions :: BuildInfo -> [Extension]otherExtensions bi :: BuildInfobi

-- | The 'Extensions' that are used by all modules in this component
--
usedExtensions :: BuildInfo -> [Extension]
usedExtensions bi = oldExtensions :: BuildInfo -> [Extension]oldExtensions bi :: BuildInfobi
                 (++) :: [a] -> [a] -> [a]++ defaultExtensions :: BuildInfo -> [Extension]defaultExtensions bi :: BuildInfobi

type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)])

emptyHookedBuildInfo :: HookedBuildInfo
emptyHookedBuildInfo = (Nothing :: Maybe aNothing, [] :: [a][])

-- |Select options for a particular Haskell compiler.
hcOptions :: CompilerFlavor -> BuildInfo -> [String]
hcOptions hc bi = [ opt :: Stringopt | (hc',opts) <- options :: BuildInfo -> [(CompilerFlavor, [String])]options bi :: BuildInfobi
                        , hc' :: CompilerFlavorhc' (==) :: Eq a => a -> a -> Bool== hc :: CompilerFlavorhc
                        , opt <- opts :: [String]opts ]

-- ------------------------------------------------------------
-- * Source repos
-- ------------------------------------------------------------

-- | Information about the source revision control system for a package.
--
-- When specifying a repo it is useful to know the meaning or intention of the
-- information as doing so enables automation. There are two obvious common
-- purposes: one is to find the repo for the latest development version, the
-- other is to find the repo for this specific release. The 'ReopKind'
-- specifies which one we mean (or another custom one).
--
-- A package can specify one or the other kind or both. Most will specify just
-- a head repo but some may want to specify a repo to reconstruct the sources
-- for this package release.
--
-- The required information is the 'RepoType' which tells us if it's using
-- 'Darcs', 'Git' for example. The 'repoLocation' and other details are
-- interpreted according to the repo type.
--
data repoLocation :: Maybe StringSourceRepo = SourceRepo {
  -- | The kind of repo. This field is required.
  repoKind     :: RepoKind,

  -- | The type of the source repository system for this repo, eg 'Darcs' or
  -- 'Git'. This field is required.
  repoType     :: Maybe RepoType,

  -- | The location of the repository. For most 'RepoType's this is a URL.
  -- This field is required.
  repoLocation :: Maybe String,

  -- | 'CVS' can put multiple \"modules\" on one server and requires a
  -- module name in addition to the location to identify a particular repo.
  -- Logically this is part of the location but unfortunately has to be
  -- specified separately. This field is required for the 'CVS' 'RepoType' and
  -- should not be given otherwise.
  repoModule   :: Maybe String,

  -- | The name or identifier of the branch, if any. Many source control
  -- systems have the notion of multiple branches in a repo that exist in the
  -- same location. For example 'Git' and 'CVS' use this while systems like
  -- 'Darcs' use different locations for different branches. This field is
  -- optional but should be used if necessary to identify the sources,
  -- especially for the 'RepoThis' repo kind.
  repoBranch   :: Maybe String,

  -- | The tag identify a particular state of the repository. This should be
  -- given for the 'RepoThis' repo kind and not for 'RepoHead' kind.
  --
  repoTag      :: Maybe String,

  -- | Some repositories contain multiple projects in different subdirectories
  -- This field specifies the subdirectory where this packages sources can be
  -- found, eg the subdirectory containing the @.cabal@ file. It is interpreted
  -- relative to the root of the repository. This field is optional. If not
  -- given the default is \".\" ie no subdirectory.
  repoSubdir   :: Maybe FilePath
}
  deriving (($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow)

-- | What this repo info is for, what it represents.
--
data RepoKind =
    -- | The repository for the \"head\" or development version of the project.
    -- This repo is where we should track the latest development activity or
    -- the usual repo people should get to contribute patches.
    RepoHead

    -- | The repository containing the sources for this exact package version
    -- or release. For this kind of repo a tag should be given to give enough
    -- information to re-create the exact sources.
  | RepoThis

  | RepoKindUnknown String
  deriving (($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq, D:Ord ::
  Eq a =>
  (a -> a -> Ordering)
  -> (a -> a -> Bool)
  -> (a -> a -> Bool)
  -> (a -> a -> Bool)
  -> (a -> a -> Bool)
  -> (a -> a -> a)
  -> (a -> a -> a)
  -> T:Ord aOrd, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow)

-- | An enumeration of common source control systems. The fields used in the
-- 'SourceRepo' depend on the type of repo. The tools and methods used to
-- obtain and track the repo depend on the repo type.
--
data RepoType = Darcs | Git | SVN | CVS
              | Mercurial | GnuArch | Bazaar | Monotone
              | OtherRepoType String
  deriving (($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq, D:Ord ::
  Eq a =>
  (a -> a -> Ordering)
  -> (a -> a -> Bool)
  -> (a -> a -> Bool)
  -> (a -> a -> Bool)
  -> (a -> a -> Bool)
  -> (a -> a -> a)
  -> (a -> a -> a)
  -> T:Ord aOrd, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead, D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow)

knownRepoTypes :: [RepoType]
knownRepoTypes = [Darcs :: RepoTypeDarcs, Git :: RepoTypeGit, SVN :: RepoTypeSVN, CVS :: RepoTypeCVS
                 ,Mercurial :: RepoTypeMercurial, GnuArch :: RepoTypeGnuArch, Bazaar :: RepoTypeBazaar, Monotone :: RepoTypeMonotone]

repoTypeAliases :: RepoType -> [String]
repoTypeAliases Bazaar    = ["bzr"]
repoTypeAliases Mercurial = ["hg"]
repoTypeAliases GnuArch   = ["arch"]
repoTypeAliases _         = [] :: [a][]

instance D:Text :: (a -> Doc) -> (forall r. ReadP r a) -> T:Text aText RepoKind where
  disp RepoHead                = text :: String -> DocDisp.text "head"
  disp RepoThis                = text :: String -> DocDisp.text "this"
  disp (RepoKindUnknown other) = text :: String -> DocDisp.text other :: BuildTypeother

  parse = do
    name <- ident :: ReadP r Stringident
    return :: Monad m => forall a. a -> m areturn ($) :: (a -> b) -> a -> b$ case lowercase :: String -> Stringlowercase name :: Stringname of
      "head" -> RepoHead :: RepoKindRepoHead
      "this" -> RepoThis :: RepoKindRepoThis
      _      -> RepoKindUnknown :: String -> RepoKindRepoKindUnknown name :: Stringname

instance D:Text :: (a -> Doc) -> (forall r. ReadP r a) -> T:Text aText RepoType where
  disp (OtherRepoType other) = text :: String -> DocDisp.text other :: BuildTypeother
  disp other                 = text :: String -> DocDisp.text (lowercase :: String -> Stringlowercase (show :: Show a => a -> Stringshow other :: BuildTypeother))
  parse = fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap classifyRepoType :: String -> RepoTypeclassifyRepoType ident :: ReadP r Stringident

classifyRepoType :: String -> RepoType
classifyRepoType s =
  case lookup :: Eq a => a -> [(a, b)] -> Maybe blookup (lowercase :: String -> Stringlowercase s :: Strings) repoTypeMap :: [(String, RepoType)]repoTypeMap of
    Just repoType' -> repoType' :: RepoTyperepoType'
    Nothing        -> OtherRepoType :: String -> RepoTypeOtherRepoType s :: Strings
  where
    repoTypeMap = [ (name :: Stringname, repoType' :: RepoTyperepoType')
                  | repoType' <- knownRepoTypes :: [RepoType]knownRepoTypes
                  , name <- display :: Text a => a -> Stringdisplay repoType' :: RepoTyperepoType' (:) :: a -> [a] -> [a]: repoTypeAliases :: RepoType -> [String]repoTypeAliases repoType' :: RepoTyperepoType' ]

ident :: Parse.ReadP r String
ident = munch1 :: (Char -> Bool) -> ReadP r StringParse.munch1 (\c -> isAlphaNum :: Char -> BoolChar.isAlphaNum c :: Charc (||) :: Bool -> Bool -> Bool|| c :: Charc (==) :: Eq a => a -> a -> Bool== '_' (||) :: Bool -> Bool -> Bool|| c :: Charc (==) :: Eq a => a -> a -> Bool== '-')

lowercase :: String -> String
lowercase = map :: (a -> b) -> [a] -> [b]map toLower :: Char -> CharChar.toLower

-- ------------------------------------------------------------
-- * Utils
-- ------------------------------------------------------------

updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription (mb_lib_bi, exe_bi) p
    = p :: PackageDescriptionp{ executables = updateExecutables ::
  [(String, BuildInfo)] -> [Executable] -> [Executable]updateExecutables exe_bi :: [(String, BuildInfo)]exe_bi    (executables :: PackageDescription -> [Executable]executables p :: PackageDescriptionp)
       , library     = updateLibrary :: Maybe BuildInfo -> Maybe Library -> Maybe LibraryupdateLibrary     mb_lib_bi :: Maybe BuildInfomb_lib_bi (library :: PackageDescription -> Maybe Librarylibrary     p :: PackageDescriptionp)
       }
    where
      updateLibrary :: Maybe BuildInfo -> Maybe Library -> Maybe Library
      updateLibrary (Just bi) (Just lib) = Just :: a -> Maybe aJust (lib :: Librarylib{libBuildInfo = bi :: BuildInfobi mappend :: Monoid a => a -> a -> a`mappend` libBuildInfo :: Library -> BuildInfolibBuildInfo lib :: Librarylib})
      updateLibrary Nothing   mb_lib     = mb_lib :: Maybe Librarymb_lib
      updateLibrary (Just _)  Nothing    = Nothing :: Maybe aNothing

      updateExecutables :: [(String, BuildInfo)] -- ^[(exeName, new buildinfo)]
                        -> [Executable]          -- ^list of executables to update
                        -> [Executable]          -- ^list with exeNames updated
      updateExecutables exe_bi' executables' = foldr :: (a -> b -> b) -> b -> [a] -> bfoldr updateExecutable ::
  (String, BuildInfo) -> [Executable] -> [Executable]updateExecutable executables' :: [Executable]executables' exe_bi' :: [(String, BuildInfo)]exe_bi'

      updateExecutable :: (String, BuildInfo) -- ^(exeName, new buildinfo)
                       -> [Executable]        -- ^list of executables to update
                       -> [Executable]        -- ^libst with exeName updated
      updateExecutable _                 []         = [] :: [a][]
      updateExecutable exe_bi'@(name,bi) (exe:exes)
        | exeName :: Executable -> StringexeName exe :: Executableexe (==) :: Eq a => a -> a -> Bool== name :: Stringname = exe :: Executableexe{buildInfo = bi :: BuildInfobi mappend :: Monoid a => a -> a -> a`mappend` buildInfo :: Executable -> BuildInfobuildInfo exe :: Executableexe} (:) :: a -> [a] -> [a]: exes :: [Executable]exes
        | otherwise :: Boolotherwise           = exe :: Executableexe (:) :: a -> [a] -> [a]: updateExecutable ::
  (String, BuildInfo) -> [Executable] -> [Executable]updateExecutable exe_bi' :: [(String, BuildInfo)]exe_bi' exes :: [Executable]exes

-- ---------------------------------------------------------------------------
-- The GenericPackageDescription type

data condExecutables ::
  [(String, CondTree ConfVar [Dependency] Executable)]GenericPackageDescription =
    GenericPackageDescription {
        packageDescription :: PackageDescription,
        genPackageFlags       :: [Flag],
        condLibrary        :: Maybe (CondTree ConfVar [Dependency] Library),
        condExecutables    :: [(String, CondTree ConfVar [Dependency] Executable)],
        condTestSuites     :: [(String, CondTree ConfVar [Dependency] TestSuite)]
      }
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

instance D:Package :: (pkg -> PackageIdentifier) -> T:Package pkgPackage GenericPackageDescription where
  packageId = packageId :: Package pkg => pkg -> PackageIdentifierpackageId (.) :: (b -> c) -> (a -> b) -> a -> c. packageDescription ::
  GenericPackageDescription -> PackageDescriptionpackageDescription

--TODO: make PackageDescription an instance of Text.

-- | A flag can represent a feature to be included, or a way of linking
--   a target against its dependencies, or in fact whatever you can think of.
data flagDescription :: StringFlag = MkFlag
    { flagName        :: FlagName
    , flagDescription :: String
    , flagDefault     :: Bool
    , flagManual      :: Bool
    }
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

-- | A 'FlagName' is the name of a user-defined configuration flag
newtype FlagName = FlagName String
    deriving (($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq, D:Ord ::
  Eq a =>
  (a -> a -> Ordering)
  -> (a -> a -> Bool)
  -> (a -> a -> Bool)
  -> (a -> a -> Bool)
  -> (a -> a -> Bool)
  -> (a -> a -> a)
  -> (a -> a -> a)
  -> T:Ord aOrd, D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, D:Read ::
  (Int -> ReadS a)
  -> ReadS [a]
  -> ReadPrec a
  -> ReadPrec [a]
  -> T:Read aRead)

-- | A 'FlagAssignment' is a total or partial mapping of 'FlagName's to
-- 'Bool' flag values. It represents the flags chosen by the user or
-- discovered during configuration. For example @--flags=foo --flags=-bar@
-- becomes @[("foo", True), ("bar", False)]@
--
type FlagAssignment = [(FlagName, Bool)]

-- | A @ConfVar@ represents the variable type used.
data ConfVar = OS OS
             | Arch Arch
             | Flag FlagName
             | Impl CompilerFlavor VersionRange
    deriving (($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq, D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow)

--instance Text ConfVar where
--    disp (OS os) = "os(" ++ display os ++ ")"
--    disp (Arch arch) = "arch(" ++ display arch ++ ")"
--    disp (Flag (ConfFlag f)) = "flag(" ++ f ++ ")"
--    disp (Impl c v) = "impl(" ++ display c
--                       ++ " " ++ display v ++ ")"

-- | A boolean expression parameterized over the variable type used.
data Condition c = Var c
                 | Lit Bool
                 | CNot (Condition c)
                 | COr (Condition c) (Condition c)
                 | CAnd (Condition c) (Condition c)
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

--instance Text c => Text (Condition c) where
--  disp (Var x) = text (show x)
--  disp (Lit b) = text (show b)
--  disp (CNot c) = char '!' <> parens (ppCond c)
--  disp (COr c1 c2) = parens $ sep [ppCond c1, text "||" <+> ppCond c2]
--  disp (CAnd c1 c2) = parens $ sep [ppCond c1, text "&&" <+> ppCond c2]

data condTreeComponents ::
  [(Condition v, CondTree v c a, Maybe (CondTree v c a))]CondTree v c a = CondNode
    { condTreeData        :: a
    , condTreeConstraints :: c
    , condTreeComponents  :: [( Condition v
                              , CondTree v c a
                              , Maybe (CondTree v c a))]
    }
    deriving (D:Show ::
  (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> T:Show aShow, ($c==) ::
  GenericPackageDescription -> GenericPackageDescription -> BoolEq)

--instance (Text v, Text c) => Text (CondTree v c a) where
--  disp (CondNode _dat cs ifs) =
--    (text "build-depends: " <+>
--      disp cs)
--    $+$
--    (vcat $ map ppIf ifs)
--  where
--    ppIf (c,thenTree,mElseTree) =
--        ((text "if" <+> ppCond c <> colon) $$
--          nest 2 (ppCondTree thenTree disp))
--        $+$ (maybe empty (\t -> text "else: " $$ nest 2 (ppCondTree t disp))
--                   mElseTree)