-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A framework for packaging Haskell software -- -- The Haskell Common Architecture for Building Applications and -- Libraries: a framework defining a common interface for authors to more -- easily build their Haskell applications in a portable way. -- -- The Haskell Cabal is part of a larger infrastructure for distributing, -- organizing, and cataloging Haskell libraries and tools. @package Cabal @version 1.22.3.0 -- | This module defines the detailed test suite interface which makes it -- possible to expose individual tests to Cabal or other test agents. module Distribution.TestSuite data TestInstance [TestInstance] :: IO Progress -> String -> [String] -> [OptionDescr] -> (String -> String -> Either String TestInstance) -> TestInstance -- | Perform the test. [run] :: TestInstance -> IO Progress -- | A name for the test, unique within a test suite. [name] :: TestInstance -> String -- | Users can select groups of tests by their tags. [tags] :: TestInstance -> [String] -- | Descriptions of the options recognized by this test. [options] :: TestInstance -> [OptionDescr] -- | Try to set the named option to the given value. Returns an error -- message if the option is not supported or the value could not be -- correctly parsed; otherwise, a TestInstance with the option set -- to the given value is returned. [setOption] :: TestInstance -> String -> String -> Either String TestInstance data OptionDescr [OptionDescr] :: String -> String -> OptionType -> Maybe String -> OptionDescr [optionName] :: OptionDescr -> String -- | A human-readable description of the option to guide the user setting -- it. [optionDescription] :: OptionDescr -> String [optionType] :: OptionDescr -> OptionType [optionDefault] :: OptionDescr -> Maybe String data OptionType [OptionFile] :: Bool -> Bool -> [String] -> OptionType [optionFileMustExist] :: OptionType -> Bool [optionFileIsDir] :: OptionType -> Bool [optionFileExtensions] :: OptionType -> [String] [OptionString] :: Bool -> OptionType [optionStringMultiline] :: OptionType -> Bool [OptionNumber] :: Bool -> (Maybe String, Maybe String) -> OptionType [optionNumberIsInt] :: OptionType -> Bool [optionNumberBounds] :: OptionType -> (Maybe String, Maybe String) [OptionBool] :: OptionType [OptionEnum] :: [String] -> OptionType [OptionSet] :: [String] -> OptionType [OptionRngSeed] :: OptionType data Test [Test] :: TestInstance -> Test [Group] :: String -> Bool -> [Test] -> Test [groupName] :: Test -> String -- | If true, then children of this group may be run in parallel. Note that -- this setting is not inherited by children. In particular, consider a -- group F with "concurrently = False" that has some children, including -- a group T with "concurrently = True". The children of group T may be -- run concurrently with each other, as long as none are run at the same -- time as any of the direct children of group F. [concurrently] :: Test -> Bool [groupTests] :: Test -> [Test] [ExtraOptions] :: [OptionDescr] -> Test -> Test type Options = [(String, String)] data Progress [Finished] :: Result -> Progress [Progress] :: String -> (IO Progress) -> Progress data Result [Pass] :: Result [Fail] :: String -> Result [Error] :: String -> Result -- | Create a named group of tests, which are assumed to be safe to run in -- parallel. testGroup :: String -> [Test] -> Test instance Show Result instance Read Result instance Eq Result instance Show OptionDescr instance Read OptionDescr instance Eq OptionDescr instance Show OptionType instance Read OptionType instance Eq OptionType -- | Remove the "literal" markups from a Haskell source file, including -- ">", "\begin{code}", "\end{code}", and -- "#" module Distribution.Simple.PreProcess.Unlit -- | unlit takes a filename (for error reports), and transforms the -- given string, to eliminate the literate comments from the program -- text. unlit :: FilePath -> String -> Either String String -- | No unliteration. plain :: String -> String -> String -- | Common utils used by modules under Distribution.PackageDescription.*. module Distribution.PackageDescription.Utils cabalBug :: String -> a userBug :: String -> a -- | This simple package provides types and functions for interacting with -- C compilers. Currently it's just a type enumerating extant C-like -- languages, which we call dialects. module Distribution.Simple.CCompiler -- | Represents a dialect of C. The Monoid instance expresses backward -- compatibility, in the sense that 'mappend a b' is the least inclusive -- dialect which both a and b can be correctly -- interpreted as. data CDialect [C] :: CDialect [ObjectiveC] :: CDialect [CPlusPlus] :: CDialect [ObjectiveCPlusPlus] :: CDialect -- | A list of all file extensions which are recognized as possibly -- containing some dialect of C code. Note that this list is only for -- source files, not for header files. cSourceExtensions :: [String] -- | Takes a dialect of C and whether code is intended to be passed through -- the preprocessor, and returns a filename extension for containing that -- code. cDialectFilenameExtension :: CDialect -> Bool -> String -- | Infers from a filename's extension the dialect of C which it contains, -- and whether it is intended to be passed through the preprocessor. filenameCDialect :: String -> Maybe (CDialect, Bool) instance Show CDialect instance Eq CDialect instance Monoid CDialect -- | This is a library of parser combinators, originally written by Koen -- Claessen. It parses all alternatives in parallel, so it never keeps -- hold of the beginning of the input string, a common source of space -- leaks with other parsers. The '(+++)' choice combinator is genuinely -- commutative; it makes no difference which branch is "shorter". -- -- See also Koen's paper Parallel Parsing Processes -- (http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.19.9217). -- -- This version of ReadP has been locally hacked to make it H98, by -- Martin Sjögren mailto:msjogren@gmail.com -- -- The unit tests have been moved to UnitTest.Distribution.Compat.ReadP, -- by Mark Lentczner mailto:mark@glyphic.com module Distribution.Compat.ReadP type ReadP r a = Parser r Char a -- | Consumes and returns the next character. Fails if there is no input -- left. get :: ReadP r Char -- | Look-ahead: returns the part of the input that is left, without -- consuming it. look :: ReadP r String -- | Symmetric choice. (+++) :: ReadP r a -> ReadP r a -> ReadP r a -- | Local, exclusive, left-biased choice: If left parser locally produces -- any result at all, then right parser is not used. (<++) :: ReadP a a -> ReadP r a -> ReadP r a -- | Transforms a parser into one that does the same, but in addition -- returns the exact characters read. IMPORTANT NOTE: gather gives -- a runtime error if its first argument is built using any occurrences -- of readS_to_P. gather :: ReadP (String -> P Char r) a -> ReadP r (String, a) -- | Always fails. pfail :: ReadP r a -- | Consumes and returns the next character, if it satisfies the specified -- predicate. satisfy :: (Char -> Bool) -> ReadP r Char -- | Parses and returns the specified character. char :: Char -> ReadP r Char -- | Parses and returns the specified string. string :: String -> ReadP r String -- | Parses the first zero or more characters satisfying the predicate. munch :: (Char -> Bool) -> ReadP r String -- | Parses the first one or more characters satisfying the predicate. munch1 :: (Char -> Bool) -> ReadP r String -- | Skips all whitespace. skipSpaces :: ReadP r () -- | Combines all parsers in the specified list. choice :: [ReadP r a] -> ReadP r a -- | count n p parses n occurrences of p in -- sequence. A list of results is returned. count :: Int -> ReadP r a -> ReadP r [a] -- | between open close p parses open, followed by -- p and finally close. Only the value of p is -- returned. between :: ReadP r open -> ReadP r close -> ReadP r a -> ReadP r a -- | option x p will either parse p or return x -- without consuming any input. option :: a -> ReadP r a -> ReadP r a -- | optional p optionally parses p and always returns -- (). optional :: ReadP r a -> ReadP r () -- | Parses zero or more occurrences of the given parser. many :: ReadP r a -> ReadP r [a] -- | Parses one or more occurrences of the given parser. many1 :: ReadP r a -> ReadP r [a] -- | Like many, but discards the result. skipMany :: ReadP r a -> ReadP r () -- | Like many1, but discards the result. skipMany1 :: ReadP r a -> ReadP r () -- | sepBy p sep parses zero or more occurrences of p, -- separated by sep. Returns a list of values returned by -- p. sepBy :: ReadP r a -> ReadP r sep -> ReadP r [a] -- | sepBy1 p sep parses one or more occurrences of p, -- separated by sep. Returns a list of values returned by -- p. sepBy1 :: ReadP r a -> ReadP r sep -> ReadP r [a] -- | endBy p sep parses zero or more occurrences of p, -- separated and ended by sep. endBy :: ReadP r a -> ReadP r sep -> ReadP r [a] -- | endBy p sep parses one or more occurrences of p, -- separated and ended by sep. endBy1 :: ReadP r a -> ReadP r sep -> ReadP r [a] -- | chainr p op x parses zero or more occurrences of p, -- separated by op. Returns a value produced by a right -- associative application of all functions returned by op. If -- there are no occurrences of p, x is returned. chainr :: ReadP r a -> ReadP r (a -> a -> a) -> a -> ReadP r a -- | chainl p op x parses zero or more occurrences of p, -- separated by op. Returns a value produced by a left -- associative application of all functions returned by op. If -- there are no occurrences of p, x is returned. chainl :: ReadP r a -> ReadP r (a -> a -> a) -> a -> ReadP r a -- | Like chainl, but parses one or more occurrences of p. chainl1 :: ReadP r a -> ReadP r (a -> a -> a) -> ReadP r a -- | Like chainr, but parses one or more occurrences of p. chainr1 :: ReadP r a -> ReadP r (a -> a -> a) -> ReadP r a -- | manyTill p end parses zero or more occurrences of p, -- until end succeeds. Returns a list of values returned by -- p. manyTill :: ReadP r a -> ReadP [a] end -> ReadP r [a] -- | A parser for a type a, represented as a function that takes a -- String and returns a list of possible parses as -- (a,String) pairs. -- -- Note that this kind of backtracking parser is very inefficient; -- reading a large structure may be quite slow (cf ReadP). type ReadS a = String -> [(a, String)] -- | Converts a parser into a Haskell ReadS-style function. This is the -- main way in which you can "run" a ReadP parser: the expanded -- type is readP_to_S :: ReadP a -> String -> [(a,String)] -- readP_to_S :: ReadP a a -> ReadS a -- | Converts a Haskell ReadS-style function into a parser. Warning: This -- introduces local backtracking in the resulting parser, and therefore a -- possible inefficiency. readS_to_P :: ReadS a -> ReadP r a instance Functor (P s) instance Applicative (P s) instance Monad (P s) instance Alternative (P s) instance MonadPlus (P s) instance Functor (Parser r s) instance Applicative (Parser r s) instance Monad (Parser r s) -- | This defines a Text class which is a bit like the Read -- and Show classes. The difference is that is uses a modern -- pretty printer and parser system and the format is not expected to be -- Haskell concrete syntax but rather the external human readable -- representation used by Cabal. module Distribution.Text class Text a disp :: Text a => a -> Doc parse :: Text a => ReadP r a display :: Text a => a -> String simpleParse :: Text a => String -> Maybe a instance Text Bool instance Text Version -- | Exports the Version type along with a parser and pretty -- printer. A version is something like "1.3.3". It also defines -- the VersionRange data types. Version ranges are like ">= -- 1.2 && < 2". module Distribution.Version -- | A Version represents the version of a software entity. -- -- An instance of Eq is provided, which implements exact equality -- modulo reordering of the tags in the versionTags field. -- -- An instance of Ord is also provided, which gives lexicographic -- ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 -- > 1.2.2, etc.). This is expected to be sufficient for many uses, -- but note that you may need to use a more specific ordering for your -- versioning scheme. For example, some versioning schemes may include -- pre-releases which have tags "pre1", "pre2", and so -- on, and these would need to be taken into account when determining -- ordering. In some cases, date ordering may be more appropriate, so the -- application would have to look for date tags in the -- versionTags field and compare those. The bottom line is, don't -- always assume that compare and other Ord operations are -- the right thing for every Version. -- -- Similarly, concrete representations of versions may differ. One -- possible concrete representation is provided (see showVersion -- and parseVersion), but depending on the application a different -- concrete representation may be more appropriate. data Version :: * [Version] :: [Int] -> [String] -> Version -- | The numeric branch for this version. This reflects the fact that most -- software versions are tree-structured; there is a main trunk which is -- tagged with versions at various points (1,2,3...), and the first -- branch off the trunk after version 3 is 3.1, the second branch off the -- trunk after version 3 is 3.2, and so on. The tree can be branched -- arbitrarily, just by adding more digits. -- -- We represent the branch as a list of Int, so version 3.2.1 -- becomes [3,2,1]. Lexicographic ordering (i.e. the default instance of -- Ord for [Int]) gives the natural ordering of branches. [versionBranch] :: Version -> [Int] -- | A version can be tagged with an arbitrary list of strings. The -- interpretation of the list of tags is entirely dependent on the entity -- that this version applies to. [versionTags] :: Version -> [String] data VersionRange -- | Deprecated: Use anyVersion, foldVersionRange or -- asVersionIntervals [AnyVersion] :: VersionRange -- | Deprecated: use thisVersion, foldVersionRange or -- asVersionIntervals [ThisVersion] :: Version -> VersionRange -- | Deprecated: use laterVersion, foldVersionRange or -- asVersionIntervals [LaterVersion] :: Version -> VersionRange -- | Deprecated: use earlierVersion, foldVersionRange or -- asVersionIntervals [EarlierVersion] :: Version -> VersionRange -- | Deprecated: use anyVersion, foldVersionRange or -- asVersionIntervals [WildcardVersion] :: Version -> VersionRange -- | Deprecated: use unionVersionRanges, foldVersionRange -- or asVersionIntervals [UnionVersionRanges] :: VersionRange -> VersionRange -> VersionRange -- | Deprecated: use intersectVersionRanges, -- foldVersionRange or asVersionIntervals [IntersectVersionRanges] :: VersionRange -> VersionRange -> VersionRange [VersionRangeParens] :: VersionRange -> VersionRange -- | The version range -any. That is, a version range containing -- all versions. -- --
--   withinRange v anyVersion = True
--   
anyVersion :: VersionRange -- | The empty version range, that is a version range containing no -- versions. -- -- This can be constructed using any unsatisfiable version range -- expression, for example > 1 && < 1. -- --
--   withinRange v noVersion = False
--   
noVersion :: VersionRange -- | The version range == v -- --
--   withinRange v' (thisVersion v) = v' == v
--   
thisVersion :: Version -> VersionRange -- | The version range || v -- --
--   withinRange v' (notThisVersion v) = v' /= v
--   
notThisVersion :: Version -> VersionRange -- | The version range > v -- --
--   withinRange v' (laterVersion v) = v' > v
--   
laterVersion :: Version -> VersionRange -- | The version range < v -- --
--   withinRange v' (earlierVersion v) = v' < v
--   
earlierVersion :: Version -> VersionRange -- | The version range >= v -- --
--   withinRange v' (orLaterVersion v) = v' >= v
--   
orLaterVersion :: Version -> VersionRange -- | The version range <= v -- --
--   withinRange v' (orEarlierVersion v) = v' <= v
--   
orEarlierVersion :: Version -> VersionRange -- | The version range vr1 || vr2 -- --
--     withinRange v' (unionVersionRanges vr1 vr2)
--   = withinRange v' vr1 || withinRange v' vr2
--   
unionVersionRanges :: VersionRange -> VersionRange -> VersionRange -- | The version range vr1 && vr2 -- --
--     withinRange v' (intersectVersionRanges vr1 vr2)
--   = withinRange v' vr1 && withinRange v' vr2
--   
intersectVersionRanges :: VersionRange -> VersionRange -> VersionRange -- | The version range == v.*. -- -- For example, for version 1.2, the version range == -- 1.2.* is the same as >= 1.2 && < 1.3 -- --
--   withinRange v' (laterVersion v) = v' >= v && v' < upper v
--     where
--       upper (Version lower t) = Version (init lower ++ [last lower + 1]) t
--   
withinVersion :: Version -> VersionRange -- | The version range >= v1 && <= v2. -- -- In practice this is not very useful because we normally use inclusive -- lower bounds and exclusive upper bounds. -- --
--   withinRange v' (laterVersion v) = v' > v
--   
-- | Deprecated: In practice this is not very useful because we normally -- use inclusive lower bounds and exclusive upper bounds betweenVersionsInclusive :: Version -> Version -> VersionRange -- | Does this version fall within the given range? -- -- This is the evaluation function for the VersionRange type. withinRange :: Version -> VersionRange -> Bool -- | Does this VersionRange place any restriction on the -- Version or is it in fact equivalent to AnyVersion. -- -- Note this is a semantic check, not simply a syntactic check. So for -- example the following is True (for all v). -- --
--   isAnyVersion (EarlierVersion v `UnionVersionRanges` orLaterVersion v)
--   
isAnyVersion :: VersionRange -> Bool -- | This is the converse of isAnyVersion. It check if the version -- range is empty, if there is no possible version that satisfies the -- version range. -- -- For example this is True (for all v): -- --
--   isNoVersion (EarlierVersion v `IntersectVersionRanges` LaterVersion v)
--   
isNoVersion :: VersionRange -> Bool -- | Is this version range in fact just a specific version? -- -- For example the version range ">= 3 && <= 3" -- contains only the version 3. isSpecificVersion :: VersionRange -> Maybe Version -- | Simplify a VersionRange expression. For non-empty version -- ranges this produces a canonical form. Empty or inconsistent version -- ranges are left as-is because that provides more information. -- -- If you need a canonical form use fromVersionIntervals . -- toVersionIntervals -- -- It satisfies the following properties: -- --
--   withinRange v (simplifyVersionRange r) = withinRange v r
--   
-- --
--       withinRange v r = withinRange v r'
--   ==> simplifyVersionRange r = simplifyVersionRange r'
--    || isNoVersion r
--    || isNoVersion r'
--   
simplifyVersionRange :: VersionRange -> VersionRange -- | Fold over the basic syntactic structure of a VersionRange. -- -- This provides a syntactic view of the expression defining the version -- range. The syntactic sugar ">= v", "<= v" and -- "== v.*" is presented in terms of the other basic syntax. -- -- For a semantic view use asVersionIntervals. foldVersionRange :: a -> (Version -> a) -> (Version -> a) -> (Version -> a) -> (a -> a -> a) -> (a -> a -> a) -> VersionRange -> a -- | An extended variant of foldVersionRange that also provides a -- view of in which the syntactic sugar ">= v", "<= -- v" and "== v.*" is presented explicitly rather than in -- terms of the other basic syntax. foldVersionRange' :: a -> (Version -> a) -> (Version -> a) -> (Version -> a) -> (Version -> a) -> (Version -> a) -> (Version -> Version -> a) -> (a -> a -> a) -> (a -> a -> a) -> (a -> a) -> VersionRange -> a -- | Given a version range, remove the highest upper bound. Example: -- (>= 1 && < 3) || (>= 4 && < 5) is -- converted to (>= 1 && || (= 4). removeUpperBound :: VersionRange -> VersionRange -- | View a VersionRange as a union of intervals. -- -- This provides a canonical view of the semantics of a -- VersionRange as opposed to the syntax of the expression used to -- define it. For the syntactic view use foldVersionRange. -- -- Each interval is non-empty. The sequence is in increasing order and no -- intervals overlap or touch. Therefore only the first and last can be -- unbounded. The sequence can be empty if the range is empty (e.g. a -- range expression like && 2). -- -- Other checks are trivial to implement using this view. For example: -- --
--   isNoVersion vr | [] <- asVersionIntervals vr = True
--                  | otherwise                   = False
--   
-- --
--   isSpecificVersion vr
--      | [(LowerBound v  InclusiveBound
--         ,UpperBound v' InclusiveBound)] <- asVersionIntervals vr
--      , v == v'   = Just v
--      | otherwise = Nothing
--   
asVersionIntervals :: VersionRange -> [VersionInterval] type VersionInterval = (LowerBound, UpperBound) data LowerBound [LowerBound] :: Version -> !Bound -> LowerBound data UpperBound [NoUpperBound] :: UpperBound [UpperBound] :: Version -> !Bound -> UpperBound data Bound [ExclusiveBound] :: Bound [InclusiveBound] :: Bound -- | A complementary representation of a VersionRange. Instead of a -- boolean version predicate it uses an increasing sequence of -- non-overlapping, non-empty intervals. -- -- The key point is that this representation gives a canonical -- representation for the semantics of VersionRanges. This makes -- it easier to check things like whether a version range is empty, -- covers all versions, or requires a certain minimum or maximum version. -- It also makes it easy to check equality or containment. It also makes -- it easier to identify 'simple' version predicates for translation into -- foreign packaging systems that do not support complex version range -- expressions. data VersionIntervals -- | Convert a VersionRange to a sequence of version intervals. toVersionIntervals :: VersionRange -> VersionIntervals -- | Convert a VersionIntervals value back into a -- VersionRange expression representing the version intervals. fromVersionIntervals :: VersionIntervals -> VersionRange -- | Test if a version falls within the version intervals. -- -- It exists mostly for completeness and testing. It satisfies the -- following properties: -- --
--   withinIntervals v (toVersionIntervals vr) = withinRange v vr
--   withinIntervals v ivs = withinRange v (fromVersionIntervals ivs)
--   
withinIntervals :: Version -> VersionIntervals -> Bool -- | Inspect the list of version intervals. versionIntervals :: VersionIntervals -> [VersionInterval] -- | Directly construct a VersionIntervals from a list of intervals. -- -- Each interval must be non-empty. The sequence must be in increasing -- order and no intervals may overlap or touch. If any of these -- conditions are not satisfied the function returns Nothing. mkVersionIntervals :: [VersionInterval] -> Maybe VersionIntervals unionVersionIntervals :: VersionIntervals -> VersionIntervals -> VersionIntervals intersectVersionIntervals :: VersionIntervals -> VersionIntervals -> VersionIntervals instance Constructor C1_7VersionRange instance Constructor C1_6VersionRange instance Constructor C1_5VersionRange instance Constructor C1_4VersionRange instance Constructor C1_3VersionRange instance Constructor C1_2VersionRange instance Constructor C1_1VersionRange instance Constructor C1_0VersionRange instance Datatype D1VersionRange instance Show VersionIntervals instance Eq VersionIntervals instance Show LowerBound instance Eq LowerBound instance Show UpperBound instance Eq UpperBound instance Show Bound instance Eq Bound instance Show VersionRange instance Read VersionRange instance Generic VersionRange instance Eq VersionRange instance Data VersionRange instance Binary VersionRange instance Binary Version instance Ord LowerBound instance Ord UpperBound instance Text VersionRange -- | Haskell language dialects and extensions module Language.Haskell.Extension -- | This represents a Haskell language dialect. -- -- Language Extensions are interpreted relative to one of these -- base languages. data Language -- | The Haskell 98 language as defined by the Haskell 98 report. -- http://haskell.org/onlinereport/ [Haskell98] :: Language -- | The Haskell 2010 language as defined by the Haskell 2010 report. -- http://www.haskell.org/onlinereport/haskell2010 [Haskell2010] :: Language -- | An unknown language, identified by its name. [UnknownLanguage] :: String -> Language knownLanguages :: [Language] -- | This represents language extensions beyond a base Language -- definition (such as Haskell98) that are supported by some -- implementations, usually in some special mode. -- -- Where applicable, references are given to an implementation's official -- documentation. data Extension -- | Enable a known extension [EnableExtension] :: KnownExtension -> Extension -- | Disable a known extension [DisableExtension] :: KnownExtension -> Extension -- | An unknown extension, identified by the name of its LANGUAGE -- pragma. [UnknownExtension] :: String -> Extension data KnownExtension -- | Allow overlapping class instances, provided there is a unique most -- specific instance for each use. -- -- [OverlappingInstances] :: KnownExtension -- | Ignore structural rules guaranteeing the termination of class instance -- resolution. Termination is guaranteed by a fixed-depth recursion -- stack, and compilation may fail if this depth is exceeded. -- -- [UndecidableInstances] :: KnownExtension -- | Implies OverlappingInstances. Allow the implementation to -- choose an instance even when it is possible that further instantiation -- of types will lead to a more specific instance being applicable. -- -- [IncoherentInstances] :: KnownExtension -- | (deprecated) Allow recursive bindings in do blocks, -- using the rec keyword. See also RecursiveDo. [DoRec] :: KnownExtension -- | Allow recursive bindings using mdo, a variant of do. -- DoRec provides a different, preferred syntax. -- -- [RecursiveDo] :: KnownExtension -- | Provide syntax for writing list comprehensions which iterate over -- several lists together, like the zipWith family of functions. -- -- [ParallelListComp] :: KnownExtension -- | Allow multiple parameters in a type class. -- -- [MultiParamTypeClasses] :: KnownExtension -- | Enable the dreaded monomorphism restriction. -- -- [MonomorphismRestriction] :: KnownExtension -- | Allow a specification attached to a multi-parameter type class which -- indicates that some parameters are entirely determined by others. The -- implementation will check that this property holds for the declared -- instances, and will use this property to reduce ambiguity in instance -- resolution. -- -- [FunctionalDependencies] :: KnownExtension -- | Like RankNTypes but does not allow a higher-rank type to itself -- appear on the left of a function arrow. -- -- [Rank2Types] :: KnownExtension -- | Allow a universally-quantified type to occur on the left of a function -- arrow. -- -- [RankNTypes] :: KnownExtension -- | Allow data constructors to have polymorphic arguments. Unlike -- RankNTypes, does not allow this for ordinary functions. -- -- [PolymorphicComponents] :: KnownExtension -- | Allow existentially-quantified data constructors. -- -- [ExistentialQuantification] :: KnownExtension -- | Cause a type variable in a signature, which has an explicit -- forall quantifier, to scope over the definition of the -- accompanying value declaration. -- -- [ScopedTypeVariables] :: KnownExtension -- | Deprecated, use ScopedTypeVariables instead. [PatternSignatures] :: KnownExtension -- | Enable implicit function parameters with dynamic scope. -- -- [ImplicitParams] :: KnownExtension -- | Relax some restrictions on the form of the context of a type -- signature. -- -- [FlexibleContexts] :: KnownExtension -- | Relax some restrictions on the form of the context of an instance -- declaration. -- -- [FlexibleInstances] :: KnownExtension -- | Allow data type declarations with no constructors. -- -- [EmptyDataDecls] :: KnownExtension -- | Run the C preprocessor on Haskell source code. -- -- [CPP] :: KnownExtension -- | Allow an explicit kind signature giving the kind of types over which a -- type variable ranges. -- -- [KindSignatures] :: KnownExtension -- | Enable a form of pattern which forces evaluation before an attempted -- match, and a form of strict let/where binding. -- -- [BangPatterns] :: KnownExtension -- | Allow type synonyms in instance heads. -- -- [TypeSynonymInstances] :: KnownExtension -- | Enable Template Haskell, a system for compile-time metaprogramming. -- -- [TemplateHaskell] :: KnownExtension -- | Enable the Foreign Function Interface. In GHC, implements the standard -- Haskell 98 Foreign Function Interface Addendum, plus some GHC-specific -- extensions. -- -- [ForeignFunctionInterface] :: KnownExtension -- | Enable arrow notation. -- -- [Arrows] :: KnownExtension -- | (deprecated) Enable generic type classes, with default -- instances defined in terms of the algebraic structure of a type. -- -- [Generics] :: KnownExtension -- | Enable the implicit importing of the module Prelude. When -- disabled, when desugaring certain built-in syntax into ordinary -- identifiers, use whatever is in scope rather than the Prelude -- -- version. -- -- [ImplicitPrelude] :: KnownExtension -- | Enable syntax for implicitly binding local names corresponding to the -- field names of a record. Puns bind specific names, unlike -- RecordWildCards. -- -- [NamedFieldPuns] :: KnownExtension -- | Enable a form of guard which matches a pattern and binds variables. -- -- [PatternGuards] :: KnownExtension -- | Allow a type declared with newtype to use deriving -- for any class with an instance for the underlying type. -- -- [GeneralizedNewtypeDeriving] :: KnownExtension -- | Enable the "Trex" extensible records system. -- -- [ExtensibleRecords] :: KnownExtension -- | Enable type synonyms which are transparent in some definitions and -- opaque elsewhere, as a way of implementing abstract datatypes. -- -- [RestrictedTypeSynonyms] :: KnownExtension -- | Enable an alternate syntax for string literals, with string -- templating. -- -- [HereDocuments] :: KnownExtension -- | Allow the character # as a postfix modifier on identifiers. -- Also enables literal syntax for unboxed values. -- -- [MagicHash] :: KnownExtension -- | Allow data types and type synonyms which are indexed by types, i.e. -- ad-hoc polymorphism for types. -- -- [TypeFamilies] :: KnownExtension -- | Allow a standalone declaration which invokes the type class -- deriving mechanism. -- -- [StandaloneDeriving] :: KnownExtension -- | Allow certain Unicode characters to stand for certain ASCII character -- sequences, e.g. keywords and punctuation. -- -- [UnicodeSyntax] :: KnownExtension -- | Allow the use of unboxed types as foreign types, e.g. in foreign -- import and foreign export. -- -- [UnliftedFFITypes] :: KnownExtension -- | Enable interruptible FFI. -- -- [InterruptibleFFI] :: KnownExtension -- | Allow use of CAPI FFI calling convention (foreign import -- capi). -- -- [CApiFFI] :: KnownExtension -- | Defer validity checking of types until after expanding type synonyms, -- relaxing the constraints on how synonyms may be used. -- -- [LiberalTypeSynonyms] :: KnownExtension -- | Allow the name of a type constructor, type class, or type variable to -- be an infix operator. [TypeOperators] :: KnownExtension -- | Enable syntax for implicitly binding local names corresponding to the -- field names of a record. A wildcard binds all unmentioned names, -- unlike NamedFieldPuns. -- -- [RecordWildCards] :: KnownExtension -- | Deprecated, use NamedFieldPuns instead. [RecordPuns] :: KnownExtension -- | Allow a record field name to be disambiguated by the type of the -- record it's in. -- -- [DisambiguateRecordFields] :: KnownExtension -- | Enable traditional record syntax (as supported by Haskell 98) -- -- [TraditionalRecordSyntax] :: KnownExtension -- | Enable overloading of string literals using a type class, much like -- integer literals. -- -- [OverloadedStrings] :: KnownExtension -- | Enable generalized algebraic data types, in which type variables may -- be instantiated on a per-constructor basis. Implies GADTSyntax. -- -- [GADTs] :: KnownExtension -- | Enable GADT syntax for declaring ordinary algebraic datatypes. -- -- [GADTSyntax] :: KnownExtension -- | Make pattern bindings monomorphic. -- -- [MonoPatBinds] :: KnownExtension -- | Relax the requirements on mutually-recursive polymorphic functions. -- -- [RelaxedPolyRec] :: KnownExtension -- | Allow default instantiation of polymorphic types in more situations. -- -- [ExtendedDefaultRules] :: KnownExtension -- | Enable unboxed tuples. -- -- [UnboxedTuples] :: KnownExtension -- | Enable deriving for classes Typeable and Data. -- -- [DeriveDataTypeable] :: KnownExtension -- | Enable deriving for Generic and Generic1. -- -- [DeriveGeneric] :: KnownExtension -- | Enable support for default signatures. -- -- [DefaultSignatures] :: KnownExtension -- | Allow type signatures to be specified in instance declarations. -- -- [InstanceSigs] :: KnownExtension -- | Allow a class method's type to place additional constraints on a class -- type variable. -- -- [ConstrainedClassMethods] :: KnownExtension -- | Allow imports to be qualified by the package name the module is -- intended to be imported from, e.g. -- --
--   import "network" Network.Socket
--   
-- -- [PackageImports] :: KnownExtension -- | (deprecated) Allow a type variable to be instantiated at a -- polymorphic type. -- -- [ImpredicativeTypes] :: KnownExtension -- | (deprecated) Change the syntax for qualified infix operators. -- -- [NewQualifiedOperators] :: KnownExtension -- | Relax the interpretation of left operator sections to allow unary -- postfix operators. -- -- [PostfixOperators] :: KnownExtension -- | Enable quasi-quotation, a mechanism for defining new concrete syntax -- for expressions and patterns. -- -- [QuasiQuotes] :: KnownExtension -- | Enable generalized list comprehensions, supporting operations such as -- sorting and grouping. -- -- [TransformListComp] :: KnownExtension -- | Enable monad comprehensions, which generalise the list comprehension -- syntax to work for any monad. -- -- [MonadComprehensions] :: KnownExtension -- | Enable view patterns, which match a value by applying a function and -- matching on the result. -- -- [ViewPatterns] :: KnownExtension -- | Allow concrete XML syntax to be used in expressions and patterns, as -- per the Haskell Server Pages extension language: -- http://www.haskell.org/haskellwiki/HSP. The ideas behind it are -- discussed in the paper "Haskell Server Pages through Dynamic Loading" -- by Niklas Broberg, from Haskell Workshop '05. [XmlSyntax] :: KnownExtension -- | Allow regular pattern matching over lists, as discussed in the paper -- "Regular Expression Patterns" by Niklas Broberg, Andreas Farre and -- Josef Svenningsson, from ICFP '04. [RegularPatterns] :: KnownExtension -- | Enable the use of tuple sections, e.g. (, True) desugars into -- x -> (x, True). -- -- [TupleSections] :: KnownExtension -- | Allow GHC primops, written in C--, to be imported into a Haskell file. [GHCForeignImportPrim] :: KnownExtension -- | Support for patterns of the form n + k, where k is -- an integer literal. -- -- [NPlusKPatterns] :: KnownExtension -- | Improve the layout rule when if expressions are used in a -- do block. [DoAndIfThenElse] :: KnownExtension -- | Enable support for multi-way if-expressions. -- -- [MultiWayIf] :: KnownExtension -- | Enable support lambda-case expressions. -- -- [LambdaCase] :: KnownExtension -- | Makes much of the Haskell sugar be desugared into calls to the -- function with a particular name that is in scope. -- -- [RebindableSyntax] :: KnownExtension -- | Make forall a keyword in types, which can be used to give the -- generalisation explicitly. -- -- [ExplicitForAll] :: KnownExtension -- | Allow contexts to be put on datatypes, e.g. the Eq a in -- data Eq a => Set a = NilSet | ConsSet a (Set a). -- -- [DatatypeContexts] :: KnownExtension -- | Local (let and where) bindings are monomorphic. -- -- [MonoLocalBinds] :: KnownExtension -- | Enable deriving for the Functor class. -- -- [DeriveFunctor] :: KnownExtension -- | Enable deriving for the Traversable class. -- -- [DeriveTraversable] :: KnownExtension -- | Enable deriving for the Foldable class. -- -- [DeriveFoldable] :: KnownExtension -- | Enable non-decreasing indentation for do blocks. -- -- [NondecreasingIndentation] :: KnownExtension -- | Allow imports to be qualified with a safe keyword that requires the -- imported module be trusted as according to the Safe Haskell definition -- of trust. -- --
--   import safe Network.Socket
--   
-- -- [SafeImports] :: KnownExtension -- | Compile a module in the Safe, Safe Haskell mode -- a restricted form -- of the Haskell language to ensure type safety. -- -- [Safe] :: KnownExtension -- | Compile a module in the Trustworthy, Safe Haskell mode -- no -- restrictions apply but the module is marked as trusted as long as the -- package the module resides in is trusted. -- -- [Trustworthy] :: KnownExtension -- | Compile a module in the Unsafe, Safe Haskell mode so that modules -- compiled using Safe, Safe Haskell mode can't import it. -- -- [Unsafe] :: KnownExtension -- | Allow type classimplicit parameterequality constraints to be -- used as types with the special kind constraint. Also generalise the -- (ctxt => ty) syntax so that any type of kind constraint -- can occur before the arrow. -- -- [ConstraintKinds] :: KnownExtension -- | Enable kind polymorphism. -- -- [PolyKinds] :: KnownExtension -- | Enable datatype promotion. -- -- [DataKinds] :: KnownExtension -- | Enable parallel arrays syntax ([:, :]) for Data -- Parallel Haskell. -- -- [ParallelArrays] :: KnownExtension -- | Enable explicit role annotations, like in (type role Foo -- representational representational). -- -- [RoleAnnotations] :: KnownExtension -- | Enable overloading of list literals, arithmetic sequences and list -- patterns using the IsList type class. -- -- [OverloadedLists] :: KnownExtension -- | Enable case expressions that have no alternatives. Also applies to -- lambda-case expressions if they are enabled. -- -- [EmptyCase] :: KnownExtension -- | Triggers the generation of derived Typeable instances for every -- datatype and type class declaration. -- -- [AutoDeriveTypeable] :: KnownExtension -- | Desugars negative literals directly (without using negate). -- -- [NegativeLiterals] :: KnownExtension -- | Allow the use of binary integer literal syntax (e.g. -- 0b11001001 to denote 201). -- -- [BinaryLiterals] :: KnownExtension -- | Allow the use of floating literal syntax for all instances of -- Num, including Int and Integer. -- -- [NumDecimals] :: KnownExtension -- | Enable support for type classes with no type parameter. -- -- [NullaryTypeClasses] :: KnownExtension -- | Enable explicit namespaces in module import/export lists. -- -- [ExplicitNamespaces] :: KnownExtension -- | Allow the user to write ambiguous types, and the type inference engine -- to infer them. -- -- [AllowAmbiguousTypes] :: KnownExtension -- | Enable foreign import javascript. [JavaScriptFFI] :: KnownExtension -- | Allow giving names to and abstracting over patterns. -- -- [PatternSynonyms] :: KnownExtension -- | Allow anonymous placeholders (underscore) inside type signatures. The -- type inference engine will generate a message describing the type -- inferred at the hole's location. -- -- [PartialTypeSignatures] :: KnownExtension -- | Allow named placeholders written with a leading underscore inside type -- signatures. Wildcards with the same name unify to the same type. -- -- [NamedWildCards] :: KnownExtension -- | Enable deriving for any class. -- -- [DeriveAnyClass] :: KnownExtension -- | Deprecated: KnownExtension is an instance of Enum and Bounded, use -- those instead. knownExtensions :: [KnownExtension] -- | Extensions that have been deprecated, possibly paired with another -- extension that replaces it. deprecatedExtensions :: [(Extension, Maybe Extension)] instance Constructor C1_2Extension instance Constructor C1_1Extension instance Constructor C1_0Extension instance Datatype D1Extension instance Constructor C1_105KnownExtension instance Constructor C1_104KnownExtension instance Constructor C1_103KnownExtension instance Constructor C1_102KnownExtension instance Constructor C1_101KnownExtension instance Constructor C1_100KnownExtension instance Constructor C1_99KnownExtension instance Constructor C1_98KnownExtension instance Constructor C1_97KnownExtension instance Constructor C1_96KnownExtension instance Constructor C1_95KnownExtension instance Constructor C1_94KnownExtension instance Constructor C1_93KnownExtension instance Constructor C1_92KnownExtension instance Constructor C1_91KnownExtension instance Constructor C1_90KnownExtension instance Constructor C1_89KnownExtension instance Constructor C1_88KnownExtension instance Constructor C1_87KnownExtension instance Constructor C1_86KnownExtension instance Constructor C1_85KnownExtension instance Constructor C1_84KnownExtension instance Constructor C1_83KnownExtension instance Constructor C1_82KnownExtension instance Constructor C1_81KnownExtension instance Constructor C1_80KnownExtension instance Constructor C1_79KnownExtension instance Constructor C1_78KnownExtension instance Constructor C1_77KnownExtension instance Constructor C1_76KnownExtension instance Constructor C1_75KnownExtension instance Constructor C1_74KnownExtension instance Constructor C1_73KnownExtension instance Constructor C1_72KnownExtension instance Constructor C1_71KnownExtension instance Constructor C1_70KnownExtension instance Constructor C1_69KnownExtension instance Constructor C1_68KnownExtension instance Constructor C1_67KnownExtension instance Constructor C1_66KnownExtension instance Constructor C1_65KnownExtension instance Constructor C1_64KnownExtension instance Constructor C1_63KnownExtension instance Constructor C1_62KnownExtension instance Constructor C1_61KnownExtension instance Constructor C1_60KnownExtension instance Constructor C1_59KnownExtension instance Constructor C1_58KnownExtension instance Constructor C1_57KnownExtension instance Constructor C1_56KnownExtension instance Constructor C1_55KnownExtension instance Constructor C1_54KnownExtension instance Constructor C1_53KnownExtension instance Constructor C1_52KnownExtension instance Constructor C1_51KnownExtension instance Constructor C1_50KnownExtension instance Constructor C1_49KnownExtension instance Constructor C1_48KnownExtension instance Constructor C1_47KnownExtension instance Constructor C1_46KnownExtension instance Constructor C1_45KnownExtension instance Constructor C1_44KnownExtension instance Constructor C1_43KnownExtension instance Constructor C1_42KnownExtension instance Constructor C1_41KnownExtension instance Constructor C1_40KnownExtension instance Constructor C1_39KnownExtension instance Constructor C1_38KnownExtension instance Constructor C1_37KnownExtension instance Constructor C1_36KnownExtension instance Constructor C1_35KnownExtension instance Constructor C1_34KnownExtension instance Constructor C1_33KnownExtension instance Constructor C1_32KnownExtension instance Constructor C1_31KnownExtension instance Constructor C1_30KnownExtension instance Constructor C1_29KnownExtension instance Constructor C1_28KnownExtension instance Constructor C1_27KnownExtension instance Constructor C1_26KnownExtension instance Constructor C1_25KnownExtension instance Constructor C1_24KnownExtension instance Constructor C1_23KnownExtension instance Constructor C1_22KnownExtension instance Constructor C1_21KnownExtension instance Constructor C1_20KnownExtension instance Constructor C1_19KnownExtension instance Constructor C1_18KnownExtension instance Constructor C1_17KnownExtension instance Constructor C1_16KnownExtension instance Constructor C1_15KnownExtension instance Constructor C1_14KnownExtension instance Constructor C1_13KnownExtension instance Constructor C1_12KnownExtension instance Constructor C1_11KnownExtension instance Constructor C1_10KnownExtension instance Constructor C1_9KnownExtension instance Constructor C1_8KnownExtension instance Constructor C1_7KnownExtension instance Constructor C1_6KnownExtension instance Constructor C1_5KnownExtension instance Constructor C1_4KnownExtension instance Constructor C1_3KnownExtension instance Constructor C1_2KnownExtension instance Constructor C1_1KnownExtension instance Constructor C1_0KnownExtension instance Datatype D1KnownExtension instance Constructor C1_2Language instance Constructor C1_1Language instance Constructor C1_0Language instance Datatype D1Language instance Data Extension instance Ord Extension instance Eq Extension instance Read Extension instance Show Extension instance Generic Extension instance Data KnownExtension instance Bounded KnownExtension instance Enum KnownExtension instance Ord KnownExtension instance Eq KnownExtension instance Read KnownExtension instance Show KnownExtension instance Generic KnownExtension instance Data Language instance Eq Language instance Read Language instance Show Language instance Generic Language instance Binary Language instance Text Language instance Binary Extension instance Binary KnownExtension instance Text Extension instance Text KnownExtension -- | This has an enumeration of the various compilers that Cabal knows -- about. It also specifies the default compiler. Sadly you'll often see -- code that does case analysis on this compiler flavour enumeration -- like: -- --
--   case compilerFlavor comp of
--     GHC -> GHC.getInstalledPackages verbosity packageDb progconf
--     JHC -> JHC.getInstalledPackages verbosity packageDb progconf
--   
-- -- Obviously it would be better to use the proper Compiler -- abstraction because that would keep all the compiler-specific code -- together. Unfortunately we cannot make this change yet without -- breaking the UserHooks api, which would break all custom -- Setup.hs files, so for the moment we just have to live with -- this deficiency. If you're interested, see ticket #57. module Distribution.Compiler data CompilerFlavor [GHC] :: CompilerFlavor [GHCJS] :: CompilerFlavor [NHC] :: CompilerFlavor [YHC] :: CompilerFlavor [Hugs] :: CompilerFlavor [HBC] :: CompilerFlavor [Helium] :: CompilerFlavor [JHC] :: CompilerFlavor [LHC] :: CompilerFlavor [UHC] :: CompilerFlavor [HaskellSuite] :: String -> CompilerFlavor [OtherCompiler] :: String -> CompilerFlavor buildCompilerId :: CompilerId buildCompilerFlavor :: CompilerFlavor -- | The default compiler flavour to pick when compiling stuff. This -- defaults to the compiler used to build the Cabal lib. -- -- However if it's not a recognised compiler then it's Nothing and -- the user will have to specify which compiler they want. defaultCompilerFlavor :: Maybe CompilerFlavor -- | Like classifyCompilerFlavor but compatible with the old ReadS -- parser. -- -- It is compatible in the sense that it accepts only the same strings, -- eg GHC but not "ghc". However other strings get mapped to -- OtherCompiler. The point of this is that we do not allow extra -- valid values that would upset older Cabal versions that had a stricter -- parser however we cope with new values more gracefully so that we'll -- be able to introduce new value in future without breaking things so -- much. parseCompilerFlavorCompat :: ReadP r CompilerFlavor data CompilerId [CompilerId] :: CompilerFlavor -> Version -> CompilerId -- | Compiler information used for resolving configurations. Some fields -- can be set to Nothing to indicate that the information is unknown. data CompilerInfo [CompilerInfo] :: CompilerId -> AbiTag -> Maybe [CompilerId] -> Maybe [Language] -> Maybe [Extension] -> CompilerInfo -- | Compiler flavour and version. [compilerInfoId] :: CompilerInfo -> CompilerId -- | Tag for distinguishing incompatible ABI's on the same architecture/os. [compilerInfoAbiTag] :: CompilerInfo -> AbiTag -- | Other implementations that this compiler claims to be compatible with, -- if known. [compilerInfoCompat] :: CompilerInfo -> Maybe [CompilerId] -- | Supported language standards, if known. [compilerInfoLanguages] :: CompilerInfo -> Maybe [Language] -- | Supported extensions, if known. [compilerInfoExtensions] :: CompilerInfo -> Maybe [Extension] -- | Make a CompilerInfo of which only the known information is its -- CompilerId, its AbiTag and that it does not claim to be compatible -- with other compiler id's. unknownCompilerInfo :: CompilerId -> AbiTag -> CompilerInfo data AbiTag [NoAbiTag] :: AbiTag [AbiTag] :: String -> AbiTag abiTagString :: AbiTag -> String instance Selector S1_0_4CompilerInfo instance Selector S1_0_3CompilerInfo instance Selector S1_0_2CompilerInfo instance Selector S1_0_1CompilerInfo instance Selector S1_0_0CompilerInfo instance Constructor C1_0CompilerInfo instance Datatype D1CompilerInfo instance Constructor C1_1AbiTag instance Constructor C1_0AbiTag instance Datatype D1AbiTag instance Constructor C1_0CompilerId instance Datatype D1CompilerId instance Constructor C1_11CompilerFlavor instance Constructor C1_10CompilerFlavor instance Constructor C1_9CompilerFlavor instance Constructor C1_8CompilerFlavor instance Constructor C1_7CompilerFlavor instance Constructor C1_6CompilerFlavor instance Constructor C1_5CompilerFlavor instance Constructor C1_4CompilerFlavor instance Constructor C1_3CompilerFlavor instance Constructor C1_2CompilerFlavor instance Constructor C1_1CompilerFlavor instance Constructor C1_0CompilerFlavor instance Datatype D1CompilerFlavor instance Read CompilerInfo instance Show CompilerInfo instance Generic CompilerInfo instance Read AbiTag instance Show AbiTag instance Generic AbiTag instance Show CompilerId instance Read CompilerId instance Ord CompilerId instance Generic CompilerId instance Eq CompilerId instance Data CompilerFlavor instance Ord CompilerFlavor instance Eq CompilerFlavor instance Read CompilerFlavor instance Show CompilerFlavor instance Generic CompilerFlavor instance Binary CompilerFlavor instance Text CompilerFlavor instance Binary CompilerId instance Text CompilerId instance Binary CompilerInfo instance Binary AbiTag instance Text AbiTag -- | This should be a much more sophisticated abstraction than it is. -- Currently it's just a bit of data about the compiler, like it's -- flavour and name and version. The reason it's just data is because -- currently it has to be in Read and Show so it can be -- saved along with the LocalBuildInfo. The only interesting bit -- of info it contains is a mapping between language extensions and -- compiler command line flags. This module also defines a -- PackageDB type which is used to refer to package databases. -- Most compilers only know about a single global package collection but -- GHC has a global and per-user one and it lets you create arbitrary -- other package databases. We do not yet fully support this latter -- feature. module Distribution.Simple.Compiler data Compiler [Compiler] :: CompilerId -> AbiTag -> [CompilerId] -> [(Language, Flag)] -> [(Extension, Flag)] -> Map String String -> Compiler -- | Compiler flavour and version. [compilerId] :: Compiler -> CompilerId -- | Tag for distinguishing incompatible ABI's on the same architecture/os. [compilerAbiTag] :: Compiler -> AbiTag -- | Other implementations that this compiler claims to be compatible with. [compilerCompat] :: Compiler -> [CompilerId] -- | Supported language standards. [compilerLanguages] :: Compiler -> [(Language, Flag)] -- | Supported extensions. [compilerExtensions] :: Compiler -> [(Extension, Flag)] -- | A key-value map for properties not covered by the above fields. [compilerProperties] :: Compiler -> Map String String showCompilerId :: Compiler -> String showCompilerIdWithAbi :: Compiler -> String compilerFlavor :: Compiler -> CompilerFlavor compilerVersion :: Compiler -> Version compilerCompatVersion :: CompilerFlavor -> Compiler -> Maybe Version compilerInfo :: Compiler -> CompilerInfo -- | Some compilers have a notion of a database of available packages. For -- some there is just one global db of packages, other compilers support -- a per-user or an arbitrary db specified at some location in the file -- system. This can be used to build isloated environments of packages, -- for example to build a collection of related packages without -- installing them globally. data PackageDB [GlobalPackageDB] :: PackageDB [UserPackageDB] :: PackageDB [SpecificPackageDB] :: FilePath -> PackageDB -- | We typically get packages from several databases, and stack them -- together. This type lets us be explicit about that stacking. For -- example typical stacks include: -- --
--   [GlobalPackageDB]
--   [GlobalPackageDB, UserPackageDB]
--   [GlobalPackageDB, SpecificPackageDB "package.conf.inplace"]
--   
-- -- Note that the GlobalPackageDB is invariably at the bottom since -- it contains the rts, base and other special compiler-specific -- packages. -- -- We are not restricted to using just the above combinations. In -- particular we can use several custom package dbs and the user package -- db together. -- -- When it comes to writing, the top most (last) package is used. type PackageDBStack = [PackageDB] -- | Return the package that we should register into. This is the package -- db at the top of the stack. registrationPackageDB :: PackageDBStack -> PackageDB -- | Make package paths absolute absolutePackageDBPaths :: PackageDBStack -> IO PackageDBStack absolutePackageDBPath :: PackageDB -> IO PackageDB -- | Some compilers support optimising. Some have different levels. For -- compilers that do not the level is just capped to the level they do -- support. data OptimisationLevel [NoOptimisation] :: OptimisationLevel [NormalOptimisation] :: OptimisationLevel [MaximumOptimisation] :: OptimisationLevel flagToOptimisationLevel :: Maybe String -> OptimisationLevel -- | Some compilers support emitting debug info. Some have different -- levels. For compilers that do not the level is just capped to the -- level they do support. data DebugInfoLevel [NoDebugInfo] :: DebugInfoLevel [MinimalDebugInfo] :: DebugInfoLevel [NormalDebugInfo] :: DebugInfoLevel [MaximalDebugInfo] :: DebugInfoLevel flagToDebugInfoLevel :: Maybe String -> DebugInfoLevel type Flag = String languageToFlags :: Compiler -> Maybe Language -> [Flag] unsupportedLanguages :: Compiler -> [Language] -> [Language] -- | For the given compiler, return the flags for the supported extensions. extensionsToFlags :: Compiler -> [Extension] -> [Flag] -- | For the given compiler, return the extensions it does not support. unsupportedExtensions :: Compiler -> [Extension] -> [Extension] -- | Does this compiler support parallel --make mode? parmakeSupported :: Compiler -> Bool -- | Does this compiler support reexported-modules? reexportedModulesSupported :: Compiler -> Bool -- | Does this compiler support thinning/renaming on package flags? renamingPackageFlagsSupported :: Compiler -> Bool -- | Does this compiler support package keys? packageKeySupported :: Compiler -> Bool instance Selector S1_0_5Compiler instance Selector S1_0_4Compiler instance Selector S1_0_3Compiler instance Selector S1_0_2Compiler instance Selector S1_0_1Compiler instance Selector S1_0_0Compiler instance Constructor C1_0Compiler instance Datatype D1Compiler instance Constructor C1_3DebugInfoLevel instance Constructor C1_2DebugInfoLevel instance Constructor C1_1DebugInfoLevel instance Constructor C1_0DebugInfoLevel instance Datatype D1DebugInfoLevel instance Constructor C1_2OptimisationLevel instance Constructor C1_1OptimisationLevel instance Constructor C1_0OptimisationLevel instance Datatype D1OptimisationLevel instance Constructor C1_2PackageDB instance Constructor C1_1PackageDB instance Constructor C1_0PackageDB instance Datatype D1PackageDB instance Read Compiler instance Show Compiler instance Generic Compiler instance Show DebugInfoLevel instance Read DebugInfoLevel instance Generic DebugInfoLevel instance Eq DebugInfoLevel instance Enum DebugInfoLevel instance Bounded DebugInfoLevel instance Show OptimisationLevel instance Read OptimisationLevel instance Generic OptimisationLevel instance Eq OptimisationLevel instance Enum OptimisationLevel instance Bounded OptimisationLevel instance Read PackageDB instance Show PackageDB instance Ord PackageDB instance Generic PackageDB instance Eq PackageDB instance Binary Compiler instance Binary PackageDB instance Binary OptimisationLevel instance Binary DebugInfoLevel -- | Package descriptions contain fields for specifying the name of a -- software license and the name of the file containing the text of that -- license. While package authors may choose any license they like, Cabal -- provides an enumeration of a small set of common free and open source -- software licenses. This is done so that Hackage can recognise -- licenses, so that tools can detect licensing conflicts, and to -- deter license proliferation. -- -- It is recommended that all package authors use the -- license-file or license-files fields in their -- package descriptions. Further information about these fields can be -- found in the Cabal users guide. -- --

Additional resources

-- -- The following websites provide information about free and open source -- software licenses: -- -- -- --

Disclaimer

-- -- The descriptions of software licenses provided by this documentation -- are intended for informational purposes only and in no way constitute -- legal advice. Please read the text of the licenses and consult a -- lawyer for any advice regarding software licensing. module Distribution.License -- | Indicates the license under which a package's source code is released. -- Versions of the licenses not listed here will be rejected by Hackage -- and cause cabal check to issue a warning. data License -- | GNU General Public License, version 2 or version 3. [GPL] :: (Maybe Version) -> License -- | GNU Affero General Public License, version 3. [AGPL] :: (Maybe Version) -> License -- | GNU Lesser General Public License, version 2.1 or version -- 3. [LGPL] :: (Maybe Version) -> License -- | 2-clause BSD license. [BSD2] :: License -- | 3-clause BSD license. [BSD3] :: License -- | 4-clause BSD license. This license has not been approved by the -- OSI and is incompatible with the GNU GPL. It is provided for -- historical reasons and should be avoided. [BSD4] :: License -- | MIT license. [MIT] :: License -- | ISC license [ISC] :: License -- | Mozilla Public License, version 2.0. [MPL] :: Version -> License -- | Apache License, version 2.0. [Apache] :: (Maybe Version) -> License -- | The author of a package disclaims any copyright to its source code and -- dedicates it to the public domain. This is not a software license. -- Please note that it is not possible to dedicate works to the public -- domain in every jurisdiction, nor is a work that is in the public -- domain in one jurisdiction necessarily in the public domain elsewhere. [PublicDomain] :: License -- | Explicitly 'All Rights Reserved', eg for proprietary software. The -- package may not be legally modified or redistributed by anyone but the -- rightsholder. [AllRightsReserved] :: License -- | No license specified which legally defaults to 'All Rights Reserved'. -- The package may not be legally modified or redistributed by anyone but -- the rightsholder. [UnspecifiedLicense] :: License -- | Any other software license. [OtherLicense] :: License -- | Indicates an erroneous license name. [UnknownLicense] :: String -> License -- | The list of all currently recognised licenses. knownLicenses :: [License] instance Constructor C1_14License instance Constructor C1_13License instance Constructor C1_12License instance Constructor C1_11License instance Constructor C1_10License instance Constructor C1_9License instance Constructor C1_8License instance Constructor C1_7License instance Constructor C1_6License instance Constructor C1_5License instance Constructor C1_4License instance Constructor C1_3License instance Constructor C1_2License instance Constructor C1_1License instance Constructor C1_0License instance Datatype D1License instance Data License instance Eq License instance Show License instance Read License instance Generic License instance Binary License instance Text License -- | Data type for Haskell module names. module Distribution.ModuleName -- | A valid Haskell module name. data ModuleName -- | Construct a ModuleName from a valid module name String. -- -- This is just a convenience function intended for valid module strings. -- It is an error if it is used with a string that is not a valid module -- name. If you are parsing user input then use simpleParse -- instead. fromString :: String -> ModuleName -- | The individual components of a hierarchical module name. For example -- --
--   components (fromString "A.B.C") = ["A", "B", "C"]
--   
components :: ModuleName -> [String] -- | Convert a module name to a file path, but without any file extension. -- For example: -- --
--   toFilePath (fromString "A.B.C") = "A/B/C"
--   
toFilePath :: ModuleName -> FilePath -- | The module name Main. main :: ModuleName -- | Deprecated: use ModuleName.fromString instead simple :: String -> ModuleName instance Constructor C1_0ModuleName instance Datatype D1ModuleName instance Data ModuleName instance Show ModuleName instance Read ModuleName instance Ord ModuleName instance Generic ModuleName instance Eq ModuleName instance Binary ModuleName instance Text ModuleName -- | Defines a package identifier along with a parser and pretty printer -- for it. PackageIdentifiers consist of a name and an exact -- version. It also defines a Dependency data type. A dependency -- is a package name and a version range, like "foo >= 1.2 -- && < 2". module Distribution.Package newtype PackageName [PackageName] :: String -> PackageName [unPackageName] :: PackageName -> String -- | The name and version of a package. data PackageIdentifier [PackageIdentifier] :: PackageName -> Version -> PackageIdentifier -- | The name of this package, eg. foo [pkgName] :: PackageIdentifier -> PackageName -- | the version of this package, eg 1.2 [pkgVersion] :: PackageIdentifier -> Version -- | Type alias so we can use the shorter name PackageId. type PackageId = PackageIdentifier -- | An InstalledPackageId uniquely identifies an instance of an installed -- package. There can be at most one package with a given -- InstalledPackageId in a package database, or overlay of -- databases. newtype InstalledPackageId [InstalledPackageId] :: String -> InstalledPackageId -- | A PackageKey is the notion of "package ID" which is visible to -- the compiler. Why is this not a PackageId? The PackageId -- is a user-visible concept written explicity in Cabal files; on the -- other hand, a PackageKey may contain, for example, information -- about the transitive dependency tree of a package. Why is this not an -- InstalledPackageId? A PackageKey affects the ABI because -- it is used for linker symbols; however, an InstalledPackageId -- can be used to distinguish two ABI-compatible versions of a library. -- -- The key is defined to be a 128-bit MD5 hash, separated into two 64-bit -- components (the most significant component coming first) which are -- individually base-62 encoded (A-Z, a-z, 0-9). -- --
--   key         ::= hash64 hash64
--   hash64      ::= [A-Za-z0-9]{11}
--   
-- -- The string that is hashed is specified as raw_key: -- --
--   raw_key     ::= package_id "n"
--                   holes_nl
--                   depends_nl
--   package_id  ::= package_name "-" package_version
--   holes_nl    ::= ""
--                 | hole_inst "n" holes_nl
--   hole_inst   ::= modulename " " key ":" modulename
--   depends_nl  ::= ""
--                 | depend "n" depends_nl
--   depend      ::= key
--   
-- -- The holes list MUST be sorted by the first modulename; the depends -- list MUST be sorted by the key. holes describes the backing -- implementations of all holes in the package; depends describes all of -- the build-depends of a package. A package key MAY be used in holes -- even if it is not mentioned in depends: depends contains STRICTLY -- packages which are textually mentioned in the package description. -- -- The trailing newline is MANDATORY. -- -- There is also a variant of package key which is prefixed by a -- informational string. This key MUST NOT be used in the computation of -- the hash proper, but it is useful for human-readable consumption. -- --
--   infokey     ::= infostring "_" key
--   infostring  ::= [A-Za-z0-9-]+
--   
-- -- For example, Cabal provides a key with the first five characters of -- the package name for linker symbols. data PackageKey -- | Modern package key which is a hash of the PackageId and the transitive -- dependency key. Manually inline it here so we can get the instances we -- need. Also contains a short informative string [PackageKey] :: !String -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> PackageKey -- | Old-style package key which is just a PackageId. Required -- because old versions of GHC assume that the sourcePackageId -- recorded for an installed package coincides with the package key it -- was compiled with. [OldPackageKey] :: !PackageId -> PackageKey -- | Generates a PackageKey from a PackageId, sorted package -- keys of the immediate dependencies. mkPackageKey :: Bool -> PackageId -> [PackageKey] -> [(ModuleName, (PackageKey, ModuleName))] -> PackageKey packageKeyHash :: PackageKey -> String packageKeyLibraryName :: PackageId -> PackageKey -> String -- | Describes a dependency on a source package (API) data Dependency [Dependency] :: PackageName -> VersionRange -> Dependency thisPackageVersion :: PackageIdentifier -> Dependency notThisPackageVersion :: PackageIdentifier -> Dependency -- | Simplify the VersionRange expression in a Dependency. -- See simplifyVersionRange. simplifyDependency :: Dependency -> Dependency -- | Class of things that have a PackageIdentifier -- -- Types in this class are all notions of a package. This allows us to -- have different types for the different phases that packages go though, -- from simple name/id, package description, configured or installed -- packages. -- -- Not all kinds of packages can be uniquely identified by a -- PackageIdentifier. In particular, installed packages cannot, -- there may be many installed instances of the same source package. class Package pkg packageId :: Package pkg => pkg -> PackageIdentifier packageName :: Package pkg => pkg -> PackageName packageVersion :: Package pkg => pkg -> Version -- | Subclass of packages that have specific versioned dependencies. -- -- So for example a not-yet-configured package has dependencies on -- version ranges, not specific versions. A configured or an already -- installed package depends on exact versions. Some operations or data -- structures (like dependency graphs) only make sense on this subclass -- of package types. class Package pkg => PackageFixedDeps pkg depends :: PackageFixedDeps pkg => pkg -> [PackageIdentifier] -- | Class of installed packages. -- -- The primary data type which is an instance of this package is -- InstalledPackageInfo, but when we are doing install plans in -- Cabal install we may have other, installed package-like things which -- contain more metadata. Installed packages have exact dependencies -- installedDepends. class Package pkg => PackageInstalled pkg installedPackageId :: PackageInstalled pkg => pkg -> InstalledPackageId installedDepends :: PackageInstalled pkg => pkg -> [InstalledPackageId] instance Constructor C1_0Dependency instance Datatype D1Dependency instance Constructor C1_1PackageKey instance Constructor C1_0PackageKey instance Datatype D1PackageKey instance Constructor C1_0InstalledPackageId instance Datatype D1InstalledPackageId instance Selector S1_0_1PackageIdentifier instance Selector S1_0_0PackageIdentifier instance Constructor C1_0PackageIdentifier instance Datatype D1PackageIdentifier instance Selector S1_0_0PackageName instance Constructor C1_0PackageName instance Datatype D1PackageName instance Data Dependency instance Eq Dependency instance Show Dependency instance Read Dependency instance Generic Dependency instance Data PackageKey instance Ord PackageKey instance Eq PackageKey instance Show PackageKey instance Read PackageKey instance Generic PackageKey instance Data InstalledPackageId instance Ord InstalledPackageId instance Eq InstalledPackageId instance Show InstalledPackageId instance Read InstalledPackageId instance Generic InstalledPackageId instance Data PackageIdentifier instance Ord PackageIdentifier instance Eq PackageIdentifier instance Show PackageIdentifier instance Read PackageIdentifier instance Generic PackageIdentifier instance Data PackageName instance Ord PackageName instance Eq PackageName instance Show PackageName instance Read PackageName instance Generic PackageName instance Binary PackageName instance Text PackageName instance NFData PackageName instance Binary PackageIdentifier instance Text PackageIdentifier instance NFData PackageIdentifier instance Binary InstalledPackageId instance Text InstalledPackageId instance Binary PackageKey instance Text PackageKey instance NFData PackageKey instance Binary Dependency instance Text Dependency instance Package PackageIdentifier -- | Cabal often needs to do slightly different things on specific -- platforms. You probably know about the os however using that is -- very inconvenient because it is a string and different Haskell -- implementations do not agree on using the same strings for the same -- platforms! (In particular see the controversy over "windows" vs -- "ming32"). So to make it more consistent and easy to use we have an -- OS enumeration. module Distribution.System data OS [Linux] :: OS [Windows] :: OS [OSX] :: OS [FreeBSD] :: OS [OpenBSD] :: OS [NetBSD] :: OS [DragonFly] :: OS [Solaris] :: OS [AIX] :: OS [HPUX] :: OS [IRIX] :: OS [HaLVM] :: OS [IOS] :: OS [Ghcjs] :: OS [OtherOS] :: String -> OS buildOS :: OS data Arch [I386] :: Arch [X86_64] :: Arch [PPC] :: Arch [PPC64] :: Arch [Sparc] :: Arch [Arm] :: Arch [Mips] :: Arch [SH] :: Arch [IA64] :: Arch [S390] :: Arch [Alpha] :: Arch [Hppa] :: Arch [Rs6000] :: Arch [M68k] :: Arch [Vax] :: Arch [JavaScript] :: Arch [OtherArch] :: String -> Arch buildArch :: Arch data Platform [Platform] :: Arch -> OS -> Platform -- | The platform Cabal was compiled on. In most cases, -- LocalBuildInfo.hostPlatform should be used instead (the -- platform we're targeting). buildPlatform :: Platform platformFromTriple :: String -> Maybe Platform instance Constructor C1_0Platform instance Datatype D1Platform instance Constructor C1_16Arch instance Constructor C1_15Arch instance Constructor C1_14Arch instance Constructor C1_13Arch instance Constructor C1_12Arch instance Constructor C1_11Arch instance Constructor C1_10Arch instance Constructor C1_9Arch instance Constructor C1_8Arch instance Constructor C1_7Arch instance Constructor C1_6Arch instance Constructor C1_5Arch instance Constructor C1_4Arch instance Constructor C1_3Arch instance Constructor C1_2Arch instance Constructor C1_1Arch instance Constructor C1_0Arch instance Datatype D1Arch instance Constructor C1_14OS instance Constructor C1_13OS instance Constructor C1_12OS instance Constructor C1_11OS instance Constructor C1_10OS instance Constructor C1_9OS instance Constructor C1_8OS instance Constructor C1_7OS instance Constructor C1_6OS instance Constructor C1_5OS instance Constructor C1_4OS instance Constructor C1_3OS instance Constructor C1_2OS instance Constructor C1_1OS instance Constructor C1_0OS instance Datatype D1OS instance Data Platform instance Read Platform instance Show Platform instance Ord Platform instance Generic Platform instance Eq Platform instance Data Arch instance Read Arch instance Show Arch instance Ord Arch instance Generic Arch instance Eq Arch instance Data OS instance Read OS instance Show OS instance Ord OS instance Generic OS instance Eq OS instance Binary OS instance Text OS instance Binary Arch instance Text Arch instance Binary Platform instance Text Platform -- | 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, TestSuite, and -- Benchmark sections each of which have associated -- BuildInfo data that's used to build the library, exe, test, or -- benchmark. 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. module Distribution.PackageDescription -- | 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 PackageDescription [PackageDescription] :: PackageIdentifier -> License -> [FilePath] -> String -> String -> String -> String -> [(CompilerFlavor, VersionRange)] -> String -> String -> String -> [SourceRepo] -> String -> String -> String -> [(String, String)] -> [Dependency] -> Either Version VersionRange -> Maybe BuildType -> Maybe Library -> [Executable] -> [TestSuite] -> [Benchmark] -> [FilePath] -> FilePath -> [FilePath] -> [FilePath] -> [FilePath] -> PackageDescription [package] :: PackageDescription -> PackageIdentifier [license] :: PackageDescription -> License [licenseFiles] :: PackageDescription -> [FilePath] [copyright] :: PackageDescription -> String [maintainer] :: PackageDescription -> String [author] :: PackageDescription -> String [stability] :: PackageDescription -> String [testedWith] :: PackageDescription -> [(CompilerFlavor, VersionRange)] [homepage] :: PackageDescription -> String [pkgUrl] :: PackageDescription -> String [bugReports] :: PackageDescription -> String [sourceRepos] :: PackageDescription -> [SourceRepo] -- | A one-line summary of this package [synopsis] :: PackageDescription -> String -- | A more verbose description of this package [description] :: PackageDescription -> String [category] :: PackageDescription -> String -- | Custom fields starting with x-, stored in a simple assoc-list. | YOU -- PROBABLY DON'T WANT TO USE THIS FIELD. This field is special! -- Depending on how far along processing the PackageDescription we are, -- the contents of this field are either nonsense, or the collected -- dependencies of *all* the components in this package. buildDepends is -- initialized by finalizePackageDescription and -- flattenPackageDescription; prior to that, dependency info is -- stored in the CondTree built around a -- GenericPackageDescription. When this resolution is done, -- dependency info is written to the inner BuildInfo and this -- field. This is all horrible, and #2066 tracks progress to get rid of -- this field. [customFieldsPD] :: PackageDescription -> [(String, String)] [buildDepends] :: PackageDescription -> [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] :: PackageDescription -> Either Version VersionRange [buildType] :: PackageDescription -> Maybe BuildType [library] :: PackageDescription -> Maybe Library [executables] :: PackageDescription -> [Executable] [testSuites] :: PackageDescription -> [TestSuite] [benchmarks] :: PackageDescription -> [Benchmark] [dataFiles] :: PackageDescription -> [FilePath] [dataDir] :: PackageDescription -> FilePath [extraSrcFiles] :: PackageDescription -> [FilePath] [extraTmpFiles] :: PackageDescription -> [FilePath] [extraDocFiles] :: PackageDescription -> [FilePath] emptyPackageDescription :: PackageDescription -- | 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 -- | 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. -- | Deprecated: Use specVersion instead descCabalVersion :: PackageDescription -> VersionRange -- | The type of build system used by this package. data BuildType -- | calls Distribution.Simple.defaultMain [Simple] :: BuildType -- | calls Distribution.Simple.defaultMainWithHooks -- defaultUserHooks, which invokes configure to generate -- additional build information used by later phases. [Configure] :: BuildType -- | calls Distribution.Make.defaultMain [Make] :: BuildType -- | uses user-supplied Setup.hs or Setup.lhs (default) [Custom] :: BuildType -- | 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. [UnknownBuildType] :: String -> BuildType knownBuildTypes :: [BuildType] -- | Renaming applied to the modules provided by a package. The boolean -- indicates whether or not to also include all of the original names of -- modules. Thus, ModuleRenaming False [] is "don't expose any -- modules, and ModuleRenaming True [(Data.Bool, -- Bool)] is, "expose all modules, but also expose -- Data.Bool as Bool". data ModuleRenaming [ModuleRenaming] :: Bool -> [(ModuleName, ModuleName)] -> ModuleRenaming defaultRenaming :: ModuleRenaming lookupRenaming :: Package pkg => pkg -> Map PackageName ModuleRenaming -> ModuleRenaming data Library [Library] :: [ModuleName] -> [ModuleReexport] -> [ModuleName] -> [ModuleName] -> Bool -> BuildInfo -> Library [exposedModules] :: Library -> [ModuleName] [reexportedModules] :: Library -> [ModuleReexport] -- | What sigs need implementations? [requiredSignatures] :: Library -> [ModuleName] -- | What sigs are visible to users? [exposedSignatures] :: Library -> [ModuleName] -- | Is the lib to be exposed by default? [libExposed] :: Library -> Bool [libBuildInfo] :: Library -> BuildInfo data ModuleReexport [ModuleReexport] :: Maybe PackageName -> ModuleName -> ModuleName -> ModuleReexport [moduleReexportOriginalPackage] :: ModuleReexport -> Maybe PackageName [moduleReexportOriginalName] :: ModuleReexport -> ModuleName [moduleReexportName] :: ModuleReexport -> ModuleName emptyLibrary :: Library -- | If the package description has a library section, call the given -- function with the library build info as argument. withLib :: PackageDescription -> (Library -> IO ()) -> IO () -- | does this package have any libraries? hasLibs :: PackageDescription -> Bool -- | Get all the module names from the library (exposed and internal -- modules) which need to be compiled. (This does not include reexports, -- which do not need to be compiled.) libModules :: Library -> [ModuleName] data Executable [Executable] :: String -> FilePath -> BuildInfo -> Executable [exeName] :: Executable -> String [modulePath] :: Executable -> FilePath [buildInfo] :: Executable -> BuildInfo emptyExecutable :: Executable -- | Perform the action on each buildable Executable in the package -- description. withExe :: PackageDescription -> (Executable -> IO ()) -> IO () -- | does this package have any executables? hasExes :: PackageDescription -> Bool -- | Get all the module names from an exe exeModules :: Executable -> [ModuleName] -- | A "test-suite" stanza in a cabal file. data TestSuite [TestSuite] :: String -> TestSuiteInterface -> BuildInfo -> Bool -> TestSuite [testName] :: TestSuite -> String [testInterface] :: TestSuite -> TestSuiteInterface [testBuildInfo] :: TestSuite -> BuildInfo [testEnabled] :: TestSuite -> Bool -- | 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 -> TestSuiteInterface -- | 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 -> TestSuiteInterface -- | A test suite that does not conform to one of the above interfaces for -- the given reason (e.g. unknown test type). [TestSuiteUnsupported] :: TestType -> TestSuiteInterface -- | The "test-type" field in the test suite stanza. data TestType -- | "type: exitcode-stdio-x.y" [TestTypeExe] :: Version -> TestType -- | "type: detailed-x.y" [TestTypeLib] :: Version -> TestType -- | Some unknown test type e.g. "type: foo" [TestTypeUnknown] :: String -> Version -> TestType testType :: TestSuite -> TestType knownTestTypes :: [TestType] emptyTestSuite :: TestSuite -- | Does this package have any test suites? hasTests :: PackageDescription -> Bool -- | Perform an action on each buildable TestSuite in a package. withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO () -- | Get all the module names from a test suite. testModules :: TestSuite -> [ModuleName] -- | Get all the enabled test suites from a package. enabledTests :: PackageDescription -> [TestSuite] -- | A "benchmark" stanza in a cabal file. data Benchmark [Benchmark] :: String -> BenchmarkInterface -> BuildInfo -> Bool -> Benchmark [benchmarkName] :: Benchmark -> String [benchmarkInterface] :: Benchmark -> BenchmarkInterface [benchmarkBuildInfo] :: Benchmark -> BuildInfo [benchmarkEnabled] :: Benchmark -> Bool -- | The benchmark interfaces that are currently defined. Each benchmark -- must specify which interface it supports. -- -- More interfaces may be defined in future, either new revisions or -- totally new interfaces. data BenchmarkInterface -- | Benchmark interface "exitcode-stdio-1.0". The benchmark 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. [BenchmarkExeV10] :: Version -> FilePath -> BenchmarkInterface -- | A benchmark that does not conform to one of the above interfaces for -- the given reason (e.g. unknown benchmark type). [BenchmarkUnsupported] :: BenchmarkType -> BenchmarkInterface -- | The "benchmark-type" field in the benchmark stanza. data BenchmarkType -- | "type: exitcode-stdio-x.y" [BenchmarkTypeExe] :: Version -> BenchmarkType -- | Some unknown benchmark type e.g. "type: foo" [BenchmarkTypeUnknown] :: String -> Version -> BenchmarkType benchmarkType :: Benchmark -> BenchmarkType knownBenchmarkTypes :: [BenchmarkType] emptyBenchmark :: Benchmark -- | Does this package have any benchmarks? hasBenchmarks :: PackageDescription -> Bool -- | Perform an action on each buildable Benchmark in a package. withBenchmark :: PackageDescription -> (Benchmark -> IO ()) -> IO () -- | Get all the module names from a benchmark. benchmarkModules :: Benchmark -> [ModuleName] -- | Get all the enabled benchmarks from a package. enabledBenchmarks :: PackageDescription -> [Benchmark] data BuildInfo [BuildInfo] :: Bool -> [Dependency] -> [String] -> [String] -> [String] -> [Dependency] -> [String] -> [FilePath] -> [FilePath] -> [FilePath] -> [ModuleName] -> Maybe Language -> [Language] -> [Extension] -> [Extension] -> [Extension] -> [String] -> [String] -> [String] -> [FilePath] -> [FilePath] -> [FilePath] -> [(CompilerFlavor, [String])] -> [(CompilerFlavor, [String])] -> [(CompilerFlavor, [String])] -> [(String, String)] -> [Dependency] -> Map PackageName ModuleRenaming -> BuildInfo -- | component is buildable here [buildable] :: BuildInfo -> Bool -- | tools needed to build this bit [buildTools] :: BuildInfo -> [Dependency] -- | options for pre-processing Haskell code [cppOptions] :: BuildInfo -> [String] -- | options for C compiler [ccOptions] :: BuildInfo -> [String] -- | options for linker [ldOptions] :: BuildInfo -> [String] -- | pkg-config packages that are used [pkgconfigDepends] :: BuildInfo -> [Dependency] -- | support frameworks for Mac OS X [frameworks] :: BuildInfo -> [String] [cSources] :: BuildInfo -> [FilePath] [jsSources] :: BuildInfo -> [FilePath] -- | where to look for the Haskell module hierarchy [hsSourceDirs] :: BuildInfo -> [FilePath] -- | non-exposed or non-main modules [otherModules] :: BuildInfo -> [ModuleName] -- | language used when not explicitly specified [defaultLanguage] :: BuildInfo -> Maybe Language -- | other languages used within the package [otherLanguages] :: BuildInfo -> [Language] -- | language extensions used by all modules [defaultExtensions] :: BuildInfo -> [Extension] -- | other language extensions used within the package [otherExtensions] :: BuildInfo -> [Extension] -- | the old extensions field, treated same as defaultExtensions [oldExtensions] :: BuildInfo -> [Extension] -- | what libraries to link with when compiling a program that uses your -- package [extraLibs] :: BuildInfo -> [String] -- | if present, overrides extraLibs when package is loaded with GHCi. [extraGHCiLibs] :: BuildInfo -> [String] [extraLibDirs] :: BuildInfo -> [String] -- | directories to find .h files [includeDirs] :: BuildInfo -> [FilePath] -- | The .h files to be found in includeDirs [includes] :: BuildInfo -> [FilePath] -- | .h files to install with the package [installIncludes] :: BuildInfo -> [FilePath] [options] :: BuildInfo -> [(CompilerFlavor, [String])] [profOptions] :: BuildInfo -> [(CompilerFlavor, [String])] [sharedOptions] :: BuildInfo -> [(CompilerFlavor, [String])] -- | Custom fields starting with x-, stored in a simple assoc-list. [customFieldsBI] :: BuildInfo -> [(String, String)] -- | Dependencies specific to a library or executable target [targetBuildDepends] :: BuildInfo -> [Dependency] [targetBuildRenaming] :: BuildInfo -> Map PackageName ModuleRenaming emptyBuildInfo :: BuildInfo -- | The BuildInfo for the library (if there is one and it's -- buildable), and all buildable executables, test suites and benchmarks. -- Useful for gathering dependencies. allBuildInfo :: PackageDescription -> [BuildInfo] -- | The Languages used by this component allLanguages :: BuildInfo -> [Language] -- | The Extensions that are used somewhere by this component allExtensions :: BuildInfo -> [Extension] -- | The Extensions that are used by all modules in this component usedExtensions :: BuildInfo -> [Extension] -- | Select options for a particular Haskell compiler. hcOptions :: CompilerFlavor -> BuildInfo -> [String] hcProfOptions :: CompilerFlavor -> BuildInfo -> [String] hcSharedOptions :: CompilerFlavor -> BuildInfo -> [String] type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)]) emptyHookedBuildInfo :: HookedBuildInfo updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription data GenericPackageDescription [GenericPackageDescription] :: PackageDescription -> [Flag] -> Maybe (CondTree ConfVar [Dependency] Library) -> [(String, CondTree ConfVar [Dependency] Executable)] -> [(String, CondTree ConfVar [Dependency] TestSuite)] -> [(String, CondTree ConfVar [Dependency] Benchmark)] -> GenericPackageDescription [packageDescription] :: GenericPackageDescription -> PackageDescription [genPackageFlags] :: GenericPackageDescription -> [Flag] [condLibrary] :: GenericPackageDescription -> Maybe (CondTree ConfVar [Dependency] Library) [condExecutables] :: GenericPackageDescription -> [(String, CondTree ConfVar [Dependency] Executable)] [condTestSuites] :: GenericPackageDescription -> [(String, CondTree ConfVar [Dependency] TestSuite)] [condBenchmarks] :: GenericPackageDescription -> [(String, CondTree ConfVar [Dependency] Benchmark)] -- | 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 Flag [MkFlag] :: FlagName -> String -> Bool -> Bool -> Flag [flagName] :: Flag -> FlagName [flagDescription] :: Flag -> String [flagDefault] :: Flag -> Bool [flagManual] :: Flag -> Bool -- | A FlagName is the name of a user-defined configuration flag newtype FlagName [FlagName] :: String -> FlagName -- | A FlagAssignment is a total or partial mapping of -- FlagNames 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)] data CondTree v c a [CondNode] :: a -> c -> [(Condition v, CondTree v c a, Maybe (CondTree v c a))] -> CondTree v c a [condTreeData] :: CondTree v c a -> a [condTreeConstraints] :: CondTree v c a -> c [condTreeComponents] :: CondTree v c a -> [(Condition v, CondTree v c a, Maybe (CondTree v c a))] -- | A ConfVar represents the variable type used. data ConfVar [OS] :: OS -> ConfVar [Arch] :: Arch -> ConfVar [Flag] :: FlagName -> ConfVar [Impl] :: CompilerFlavor -> VersionRange -> ConfVar -- | A boolean expression parameterized over the variable type used. data Condition c [Var] :: c -> Condition c [Lit] :: Bool -> Condition c [CNot] :: (Condition c) -> Condition c [COr] :: (Condition c) -> (Condition c) -> Condition c [CAnd] :: (Condition c) -> (Condition c) -> Condition c -- | 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 SourceRepo [SourceRepo] :: RepoKind -> Maybe RepoType -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe FilePath -> SourceRepo -- | The kind of repo. This field is required. [repoKind] :: SourceRepo -> RepoKind -- | The type of the source repository system for this repo, eg -- Darcs or Git. This field is required. [repoType] :: SourceRepo -> Maybe RepoType -- | The location of the repository. For most RepoTypes this is a -- URL. This field is required. [repoLocation] :: SourceRepo -> 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] :: SourceRepo -> 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] :: SourceRepo -> 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] :: SourceRepo -> 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] :: SourceRepo -> Maybe FilePath -- | 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] :: RepoKind -- | 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] :: RepoKind [RepoKindUnknown] :: String -> RepoKind -- | 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] :: RepoType [Git] :: RepoType [SVN] :: RepoType [CVS] :: RepoType [Mercurial] :: RepoType [GnuArch] :: RepoType [Bazaar] :: RepoType [Monotone] :: RepoType [OtherRepoType] :: String -> RepoType knownRepoTypes :: [RepoType] instance Constructor C1_0FlagName instance Datatype D1FlagName instance Selector S1_0_27PackageDescription instance Selector S1_0_26PackageDescription instance Selector S1_0_25PackageDescription instance Selector S1_0_24PackageDescription instance Selector S1_0_23PackageDescription instance Selector S1_0_22PackageDescription instance Selector S1_0_21PackageDescription instance Selector S1_0_20PackageDescription instance Selector S1_0_19PackageDescription instance Selector S1_0_18PackageDescription instance Selector S1_0_17PackageDescription instance Selector S1_0_16PackageDescription instance Selector S1_0_15PackageDescription instance Selector S1_0_14PackageDescription instance Selector S1_0_13PackageDescription instance Selector S1_0_12PackageDescription instance Selector S1_0_11PackageDescription instance Selector S1_0_10PackageDescription instance Selector S1_0_9PackageDescription instance Selector S1_0_8PackageDescription instance Selector S1_0_7PackageDescription instance Selector S1_0_6PackageDescription instance Selector S1_0_5PackageDescription instance Selector S1_0_4PackageDescription instance Selector S1_0_3PackageDescription instance Selector S1_0_2PackageDescription instance Selector S1_0_1PackageDescription instance Selector S1_0_0PackageDescription instance Constructor C1_0PackageDescription instance Datatype D1PackageDescription instance Selector S1_0_6SourceRepo instance Selector S1_0_5SourceRepo instance Selector S1_0_4SourceRepo instance Selector S1_0_3SourceRepo instance Selector S1_0_2SourceRepo instance Selector S1_0_1SourceRepo instance Selector S1_0_0SourceRepo instance Constructor C1_0SourceRepo instance Datatype D1SourceRepo instance Constructor C1_8RepoType instance Constructor C1_7RepoType instance Constructor C1_6RepoType instance Constructor C1_5RepoType instance Constructor C1_4RepoType instance Constructor C1_3RepoType instance Constructor C1_2RepoType instance Constructor C1_1RepoType instance Constructor C1_0RepoType instance Datatype D1RepoType instance Constructor C1_2RepoKind instance Constructor C1_1RepoKind instance Constructor C1_0RepoKind instance Datatype D1RepoKind instance Selector S1_0_5Library instance Selector S1_0_4Library instance Selector S1_0_3Library instance Selector S1_0_2Library instance Selector S1_0_1Library instance Selector S1_0_0Library instance Constructor C1_0Library instance Datatype D1Library instance Selector S1_0_2Executable instance Selector S1_0_1Executable instance Selector S1_0_0Executable instance Constructor C1_0Executable instance Datatype D1Executable instance Selector S1_0_3TestSuite instance Selector S1_0_2TestSuite instance Selector S1_0_1TestSuite instance Selector S1_0_0TestSuite instance Constructor C1_0TestSuite instance Datatype D1TestSuite instance Selector S1_0_3Benchmark instance Selector S1_0_2Benchmark instance Selector S1_0_1Benchmark instance Selector S1_0_0Benchmark instance Constructor C1_0Benchmark instance Datatype D1Benchmark instance Selector S1_0_27BuildInfo instance Selector S1_0_26BuildInfo instance Selector S1_0_25BuildInfo instance Selector S1_0_24BuildInfo instance Selector S1_0_23BuildInfo instance Selector S1_0_22BuildInfo instance Selector S1_0_21BuildInfo instance Selector S1_0_20BuildInfo instance Selector S1_0_19BuildInfo instance Selector S1_0_18BuildInfo instance Selector S1_0_17BuildInfo instance Selector S1_0_16BuildInfo instance Selector S1_0_15BuildInfo instance Selector S1_0_14BuildInfo instance Selector S1_0_13BuildInfo instance Selector S1_0_12BuildInfo instance Selector S1_0_11BuildInfo instance Selector S1_0_10BuildInfo instance Selector S1_0_9BuildInfo instance Selector S1_0_8BuildInfo instance Selector S1_0_7BuildInfo instance Selector S1_0_6BuildInfo instance Selector S1_0_5BuildInfo instance Selector S1_0_4BuildInfo instance Selector S1_0_3BuildInfo instance Selector S1_0_2BuildInfo instance Selector S1_0_1BuildInfo instance Selector S1_0_0BuildInfo instance Constructor C1_0BuildInfo instance Datatype D1BuildInfo instance Constructor C1_1BenchmarkInterface instance Constructor C1_0BenchmarkInterface instance Datatype D1BenchmarkInterface instance Constructor C1_1BenchmarkType instance Constructor C1_0BenchmarkType instance Datatype D1BenchmarkType instance Constructor C1_2TestSuiteInterface instance Constructor C1_1TestSuiteInterface instance Constructor C1_0TestSuiteInterface instance Datatype D1TestSuiteInterface instance Constructor C1_2TestType instance Constructor C1_1TestType instance Constructor C1_0TestType instance Datatype D1TestType instance Selector S1_0_2ModuleReexport instance Selector S1_0_1ModuleReexport instance Selector S1_0_0ModuleReexport instance Constructor C1_0ModuleReexport instance Datatype D1ModuleReexport instance Constructor C1_0ModuleRenaming instance Datatype D1ModuleRenaming instance Constructor C1_4BuildType instance Constructor C1_3BuildType instance Constructor C1_2BuildType instance Constructor C1_1BuildType instance Constructor C1_0BuildType instance Datatype D1BuildType instance Data GenericPackageDescription instance Eq GenericPackageDescription instance Show GenericPackageDescription instance (Data v, Data c, Data a) => Data (CondTree v c a) instance (Eq v, Eq c, Eq a) => Eq (CondTree v c a) instance (Show v, Show c, Show a) => Show (CondTree v c a) instance Data c => Data (Condition c) instance Eq c => Eq (Condition c) instance Show c => Show (Condition c) instance Data ConfVar instance Show ConfVar instance Eq ConfVar instance Data Flag instance Eq Flag instance Show Flag instance Data FlagName instance Read FlagName instance Show FlagName instance Ord FlagName instance Generic FlagName instance Eq FlagName instance Data PackageDescription instance Eq PackageDescription instance Read PackageDescription instance Show PackageDescription instance Generic PackageDescription instance Data SourceRepo instance Show SourceRepo instance Read SourceRepo instance Generic SourceRepo instance Eq SourceRepo instance Data RepoType instance Show RepoType instance Read RepoType instance Ord RepoType instance Generic RepoType instance Eq RepoType instance Data RepoKind instance Show RepoKind instance Read RepoKind instance Ord RepoKind instance Generic RepoKind instance Eq RepoKind instance Data Library instance Read Library instance Eq Library instance Show Library instance Generic Library instance Data Executable instance Eq Executable instance Read Executable instance Show Executable instance Generic Executable instance Data TestSuite instance Eq TestSuite instance Read TestSuite instance Show TestSuite instance Generic TestSuite instance Data Benchmark instance Eq Benchmark instance Read Benchmark instance Show Benchmark instance Generic Benchmark instance Data BuildInfo instance Eq BuildInfo instance Read BuildInfo instance Show BuildInfo instance Generic BuildInfo instance Data BenchmarkInterface instance Show BenchmarkInterface instance Read BenchmarkInterface instance Generic BenchmarkInterface instance Eq BenchmarkInterface instance Data BenchmarkType instance Eq BenchmarkType instance Read BenchmarkType instance Show BenchmarkType instance Generic BenchmarkType instance Data TestSuiteInterface instance Show TestSuiteInterface instance Read TestSuiteInterface instance Generic TestSuiteInterface instance Eq TestSuiteInterface instance Data TestType instance Eq TestType instance Read TestType instance Show TestType instance Generic TestType instance Data ModuleReexport instance Show ModuleReexport instance Read ModuleReexport instance Generic ModuleReexport instance Eq ModuleReexport instance Generic ModuleRenaming instance Data ModuleRenaming instance Ord ModuleRenaming instance Eq ModuleRenaming instance Read ModuleRenaming instance Show ModuleRenaming instance Data BuildType instance Eq BuildType instance Read BuildType instance Show BuildType instance Generic BuildType instance Binary PackageDescription instance Package PackageDescription instance Binary BuildType instance Text BuildType instance Binary ModuleRenaming instance Monoid ModuleRenaming instance Text ModuleRenaming instance Binary Library instance Monoid Library instance Binary ModuleReexport instance Text ModuleReexport instance Binary Executable instance Monoid Executable instance Binary TestSuite instance Binary TestSuiteInterface instance Monoid TestSuite instance Monoid TestSuiteInterface instance Binary TestType instance Text TestType instance Binary Benchmark instance Binary BenchmarkInterface instance Monoid Benchmark instance Monoid BenchmarkInterface instance Binary BenchmarkType instance Text BenchmarkType instance Binary BuildInfo instance Monoid BuildInfo instance Binary SourceRepo instance Binary RepoKind instance Binary RepoType instance Text RepoKind instance Text RepoType instance Package GenericPackageDescription instance Binary FlagName -- | This manages everything to do with where files get installed (though -- does not get involved with actually doing any installation). It -- provides an InstallDirs type which is a set of directories for -- where to install things. It also handles the fact that we use -- templates in these install dirs. For example most install dirs are -- relative to some $prefix and by changing the prefix all other -- dirs still end up changed appropriately. So it provides a -- PathTemplate type and functions for substituting for these -- templates. module Distribution.Simple.InstallDirs -- | The directories where we will install files for packages. -- -- We have several different directories for different types of files -- since many systems have conventions whereby different types of files -- in a package are installed in different directories. This is -- particularly the case on Unix style systems. data InstallDirs dir [InstallDirs] :: dir -> dir -> dir -> dir -> dir -> dir -> dir -> dir -> dir -> dir -> dir -> dir -> dir -> dir -> InstallDirs dir [prefix] :: InstallDirs dir -> dir [bindir] :: InstallDirs dir -> dir [libdir] :: InstallDirs dir -> dir [libsubdir] :: InstallDirs dir -> dir [dynlibdir] :: InstallDirs dir -> dir [libexecdir] :: InstallDirs dir -> dir [includedir] :: InstallDirs dir -> dir [datadir] :: InstallDirs dir -> dir [datasubdir] :: InstallDirs dir -> dir [docdir] :: InstallDirs dir -> dir [mandir] :: InstallDirs dir -> dir [htmldir] :: InstallDirs dir -> dir [haddockdir] :: InstallDirs dir -> dir [sysconfdir] :: InstallDirs dir -> dir -- | The installation directories in terms of PathTemplates that -- contain variables. -- -- The defaults for most of the directories are relative to each other, -- in particular they are all relative to a single prefix. This makes it -- convenient for the user to override the default installation directory -- by only having to specify --prefix=... rather than overriding each -- individually. This is done by allowing $-style variables in the dirs. -- These are expanded by textual substitution (see -- substPathTemplate). -- -- A few of these installation directories are split into two components, -- the dir and subdir. The full installation path is formed by combining -- the two together with /. The reason for this is compatibility -- with other Unix build systems which also support --libdir and -- --datadir. We would like users to be able to configure -- --libdir=/usr/lib64 for example but because by default we -- want to support installing multiple versions of packages and building -- the same package for multiple compilers we append the libsubdir to -- get: /usr/lib64/$pkgkey/$compiler. -- -- An additional complication is the need to support relocatable packages -- on systems which support such things, like Windows. type InstallDirTemplates = InstallDirs PathTemplate defaultInstallDirs :: CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates combineInstallDirs :: (a -> b -> c) -> InstallDirs a -> InstallDirs b -> InstallDirs c -- | Convert from abstract install directories to actual absolute ones by -- substituting for all the variables in the abstract paths, to get real -- absolute path. absoluteInstallDirs :: PackageIdentifier -> PackageKey -> CompilerInfo -> CopyDest -> Platform -> InstallDirs PathTemplate -> InstallDirs FilePath -- | The location prefix for the copy command. data CopyDest [NoCopyDest] :: CopyDest [CopyTo] :: FilePath -> CopyDest -- | Check which of the paths are relative to the installation $prefix. -- -- If any of the paths are not relative, ie they are absolute paths, then -- it prevents us from making a relocatable package (also known as a -- "prefix independent" package). prefixRelativeInstallDirs :: PackageIdentifier -> PackageKey -> CompilerInfo -> Platform -> InstallDirTemplates -> InstallDirs (Maybe FilePath) -- | Substitute the install dir templates into each other. -- -- To prevent cyclic substitutions, only some variables are allowed in -- particular dir templates. If out of scope vars are present, they are -- not substituted for. Checking for any remaining unsubstituted vars can -- be done as a subsequent operation. -- -- The reason it is done this way is so that in -- prefixRelativeInstallDirs we can replace prefix with the -- PrefixVar and get resulting PathTemplates that still -- have the PrefixVar in them. Doing this makes it each to check -- which paths are relative to the $prefix. substituteInstallDirTemplates :: PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates -- | An abstract path, possibly containing variables that need to be -- substituted for to get a real FilePath. data PathTemplate data PathTemplateVariable -- | The $prefix path variable [PrefixVar] :: PathTemplateVariable -- | The $bindir path variable [BindirVar] :: PathTemplateVariable -- | The $libdir path variable [LibdirVar] :: PathTemplateVariable -- | The $libsubdir path variable [LibsubdirVar] :: PathTemplateVariable -- | The $datadir path variable [DatadirVar] :: PathTemplateVariable -- | The $datasubdir path variable [DatasubdirVar] :: PathTemplateVariable -- | The $docdir path variable [DocdirVar] :: PathTemplateVariable -- | The $htmldir path variable [HtmldirVar] :: PathTemplateVariable -- | The $pkg package name path variable [PkgNameVar] :: PathTemplateVariable -- | The $version package version path variable [PkgVerVar] :: PathTemplateVariable -- | The $pkgid package Id path variable, eg foo-1.0 [PkgIdVar] :: PathTemplateVariable -- | The $pkgkey package key path variable [PkgKeyVar] :: PathTemplateVariable -- | The compiler name and version, eg ghc-6.6.1 [CompilerVar] :: PathTemplateVariable -- | The operating system name, eg windows or linux [OSVar] :: PathTemplateVariable -- | The CPU architecture name, eg i386 or x86_64 [ArchVar] :: PathTemplateVariable -- | The Compiler's ABI identifier, $arch-$os-$compiler-$abitag [AbiVar] :: PathTemplateVariable -- | The optional ABI tag for the compiler [AbiTagVar] :: PathTemplateVariable -- | The executable name; used in shell wrappers [ExecutableNameVar] :: PathTemplateVariable -- | The name of the test suite being run [TestSuiteNameVar] :: PathTemplateVariable -- | The result of the test suite being run, eg pass, -- fail, or error. [TestSuiteResultVar] :: PathTemplateVariable -- | The name of the benchmark being run [BenchmarkNameVar] :: PathTemplateVariable type PathTemplateEnv = [(PathTemplateVariable, PathTemplate)] -- | Convert a FilePath to a PathTemplate including any -- template vars. toPathTemplate :: FilePath -> PathTemplate -- | Convert back to a path, any remaining vars are included fromPathTemplate :: PathTemplate -> FilePath substPathTemplate :: PathTemplateEnv -> PathTemplate -> PathTemplate -- | The initial environment has all the static stuff but no paths initialPathTemplateEnv :: PackageIdentifier -> PackageKey -> CompilerInfo -> Platform -> PathTemplateEnv platformTemplateEnv :: Platform -> PathTemplateEnv compilerTemplateEnv :: CompilerInfo -> PathTemplateEnv packageTemplateEnv :: PackageIdentifier -> PackageKey -> PathTemplateEnv abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv installDirsTemplateEnv :: InstallDirs PathTemplate -> PathTemplateEnv instance Constructor C1_0PathTemplate instance Datatype D1PathTemplate instance Constructor C1_1PathComponent instance Constructor C1_0PathComponent instance Datatype D1PathComponent instance Constructor C1_20PathTemplateVariable instance Constructor C1_19PathTemplateVariable instance Constructor C1_18PathTemplateVariable instance Constructor C1_17PathTemplateVariable instance Constructor C1_16PathTemplateVariable instance Constructor C1_15PathTemplateVariable instance Constructor C1_14PathTemplateVariable instance Constructor C1_13PathTemplateVariable instance Constructor C1_12PathTemplateVariable instance Constructor C1_11PathTemplateVariable instance Constructor C1_10PathTemplateVariable instance Constructor C1_9PathTemplateVariable instance Constructor C1_8PathTemplateVariable instance Constructor C1_7PathTemplateVariable instance Constructor C1_6PathTemplateVariable instance Constructor C1_5PathTemplateVariable instance Constructor C1_4PathTemplateVariable instance Constructor C1_3PathTemplateVariable instance Constructor C1_2PathTemplateVariable instance Constructor C1_1PathTemplateVariable instance Constructor C1_0PathTemplateVariable instance Datatype D1PathTemplateVariable instance Selector S1_0_13InstallDirs instance Selector S1_0_12InstallDirs instance Selector S1_0_11InstallDirs instance Selector S1_0_10InstallDirs instance Selector S1_0_9InstallDirs instance Selector S1_0_8InstallDirs instance Selector S1_0_7InstallDirs instance Selector S1_0_6InstallDirs instance Selector S1_0_5InstallDirs instance Selector S1_0_4InstallDirs instance Selector S1_0_3InstallDirs instance Selector S1_0_2InstallDirs instance Selector S1_0_1InstallDirs instance Selector S1_0_0InstallDirs instance Constructor C1_0InstallDirs instance Datatype D1InstallDirs instance Ord PathTemplate instance Generic PathTemplate instance Eq PathTemplate instance Generic PathComponent instance Ord PathComponent instance Eq PathComponent instance Generic PathTemplateVariable instance Ord PathTemplateVariable instance Eq PathTemplateVariable instance Show CopyDest instance Eq CopyDest instance Show dir => Show (InstallDirs dir) instance Read dir => Read (InstallDirs dir) instance Generic (InstallDirs dir) instance Binary dir => Binary (InstallDirs dir) instance Functor InstallDirs instance Monoid dir => Monoid (InstallDirs dir) instance Binary PathTemplate instance Binary PathComponent instance Binary PathTemplateVariable instance Show PathTemplateVariable instance Read PathTemplateVariable instance Show PathComponent instance Read PathComponent instance Show PathTemplate instance Read PathTemplate -- | Simple parsing with failure module Distribution.ReadE -- | Parser with simple error reporting newtype ReadE a [ReadE] :: (String -> Either ErrorMsg a) -> ReadE a [runReadE] :: ReadE a -> String -> Either ErrorMsg a succeedReadE :: (String -> a) -> ReadE a failReadE :: ErrorMsg -> ReadE a parseReadE :: ReadE a -> ReadP r a readEOrFail :: ReadE a -> String -> a readP_to_E :: (String -> ErrorMsg) -> ReadP a a -> ReadE a instance Functor ReadE -- | A simple Verbosity type with associated utilities. There are 4 -- standard verbosity levels from silent, normal, -- verbose up to deafening. This is used for deciding what -- logging messages to print. module Distribution.Verbosity data Verbosity silent :: Verbosity normal :: Verbosity verbose :: Verbosity deafening :: Verbosity moreVerbose :: Verbosity -> Verbosity lessVerbose :: Verbosity -> Verbosity intToVerbosity :: Int -> Maybe Verbosity flagToVerbosity :: ReadE Verbosity showForCabal :: Verbosity -> String showForGHC :: Verbosity -> String instance Constructor C1_3Verbosity instance Constructor C1_2Verbosity instance Constructor C1_1Verbosity instance Constructor C1_0Verbosity instance Datatype D1Verbosity instance Bounded Verbosity instance Enum Verbosity instance Ord Verbosity instance Eq Verbosity instance Read Verbosity instance Show Verbosity instance Generic Verbosity instance Binary Verbosity module Distribution.Compat.Exception catchIO :: IO a -> (IOException -> IO a) -> IO a catchExit :: IO a -> (ExitCode -> IO a) -> IO a tryIO :: IO a -> IO (Either IOException a) -- | A large and somewhat miscellaneous collection of utility functions -- used throughout the rest of the Cabal lib and in other tools that use -- the Cabal lib like cabal-install. It has a very simple set of -- logging actions. It has low level functions for running programs, a -- bunch of wrappers for various directory and file functions that do -- extra logging. module Distribution.Simple.Utils cabalVersion :: Version die :: String -> IO a dieWithLocation :: FilePath -> Maybe Int -> String -> IO a topHandler :: IO a -> IO a topHandlerWith :: (IOException -> IO a) -> IO a -> IO a -- | Non fatal conditions that may be indicative of an error or problem. -- -- We display these at the normal verbosity level. warn :: Verbosity -> String -> IO () -- | Useful status messages. -- -- We display these at the normal verbosity level. -- -- This is for the ordinary helpful status messages that users see. Just -- enough information to know that things are working but not floods of -- detail. notice :: Verbosity -> String -> IO () setupMessage :: Verbosity -> String -> PackageIdentifier -> IO () -- | More detail on the operation of some action. -- -- We display these messages when the verbosity level is verbose info :: Verbosity -> String -> IO () -- | Detailed internal debugging information -- -- We display these messages when the verbosity level is deafening debug :: Verbosity -> String -> IO () -- | A variant of debug that doesn't perform the automatic line -- wrapping. Produces better output in some cases. debugNoWrap :: Verbosity -> String -> IO () -- | Perform an IO action, catching any IO exceptions and printing an error -- if one occurs. chattyTry :: String -> IO () -> IO () printRawCommandAndArgs :: Verbosity -> FilePath -> [String] -> IO () printRawCommandAndArgsAndEnv :: Verbosity -> FilePath -> [String] -> Maybe [(String, String)] -> IO () rawSystemExit :: Verbosity -> FilePath -> [String] -> IO () rawSystemExitCode :: Verbosity -> FilePath -> [String] -> IO ExitCode rawSystemExitWithEnv :: Verbosity -> FilePath -> [String] -> [(String, String)] -> IO () -- | Run a command and return its output. -- -- The output is assumed to be text in the locale encoding. rawSystemStdout :: Verbosity -> FilePath -> [String] -> IO String -- | Run a command and return its output, errors and exit status. -- Optionally also supply some input. Also provides control over whether -- the binary/text mode of the input and output. rawSystemStdInOut :: Verbosity -> FilePath -> [String] -> Maybe FilePath -> Maybe [(String, String)] -> Maybe (String, Bool) -> Bool -> IO (String, String, ExitCode) rawSystemIOWithEnv :: Verbosity -> FilePath -> [String] -> Maybe FilePath -> Maybe [(String, String)] -> Maybe Handle -> Maybe Handle -> Maybe Handle -> IO ExitCode maybeExit :: IO ExitCode -> IO () -- | Like the Unix xargs program. Useful for when we've got very long -- command lines that might overflow an OS limit on command line length -- and so you need to invoke a command multiple times to get all the args -- in. -- -- Use it with either of the rawSystem variants above. For example: -- --
--   xargs (32*1024) (rawSystemExit verbosity) prog fixedArgs bigArgs
--   
xargs :: Int -> ([String] -> IO ()) -> [String] -> [String] -> IO () -- | Look for a program on the path. findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath) -- | Look for a program and try to find it's version number. It can accept -- either an absolute path or the name of a program binary, in which case -- we will look for the program on the path. findProgramVersion :: String -> (String -> String) -> Verbosity -> FilePath -> IO (Maybe Version) -- | Deprecated: Use findModuleFiles and copyFiles or -- installOrdinaryFiles smartCopySources :: Verbosity -> [FilePath] -> FilePath -> [ModuleName] -> [String] -> IO () -- | Same as createDirectoryIfMissing but logs at higher verbosity -- levels. createDirectoryIfMissingVerbose :: Verbosity -> Bool -> FilePath -> IO () -- | Copies a file without copying file permissions. The target file is -- created with default permissions. Any existing target file is -- replaced. -- -- At higher verbosity levels it logs an info message. copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO () -- | Deprecated: You probably want installDirectoryContents instead copyDirectoryRecursiveVerbose :: Verbosity -> FilePath -> FilePath -> IO () -- | Copies a bunch of files to a target directory, preserving the -- directory structure in the target location. The target directories are -- created if they do not exist. -- -- The files are identified by a pair of base directory and a path -- relative to that base. It is only the relative part that is preserved -- in the destination. -- -- For example: -- --
--   copyFiles normal "dist/src"
--      [("", "src/Foo.hs"), ("dist/build/", "src/Bar.hs")]
--   
-- -- This would copy "src/Foo.hs" to "dist/src/src/Foo.hs" and copy -- "dist/build/src/Bar.hs" to "dist/src/src/Bar.hs". -- -- This operation is not atomic. Any IO failure during the copy -- (including any missing source files) leaves the target in an unknown -- state so it is best to use it with a freshly created directory so that -- it can be simply deleted if anything goes wrong. copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () -- | Given a relative path to a file, copy it to the given directory, -- preserving the relative path and creating the parent directories if -- needed. copyFileTo :: Verbosity -> FilePath -> FilePath -> IO () -- | Install an ordinary file. This is like a file copy but the permissions -- are set appropriately for an installed file. On Unix it is -- "-rw-r--r--" while on Windows it uses the default permissions for the -- target directory. installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO () -- | Install an executable file. This is like a file copy but the -- permissions are set appropriately for an installed file. On Unix it is -- "-rwxr-xr-x" while on Windows it uses the default permissions for the -- target directory. installExecutableFile :: Verbosity -> FilePath -> FilePath -> IO () -- | Install a file that may or not be executable, preserving permissions. installMaybeExecutableFile :: Verbosity -> FilePath -> FilePath -> IO () -- | This is like copyFiles but uses installOrdinaryFile. installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () -- | This is like copyFiles but uses installExecutableFile. installExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () -- | This is like copyFiles but uses -- installMaybeExecutableFile. installMaybeExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () -- | This installs all the files in a directory to a target location, -- preserving the directory layout. All the files are assumed to be -- ordinary rather than executable files. installDirectoryContents :: Verbosity -> FilePath -> FilePath -> IO () -- | Recursively copy the contents of one directory to another path. copyDirectoryRecursive :: Verbosity -> FilePath -> FilePath -> IO () -- | Like doesFileExist, but also checks that the file is -- executable. doesExecutableExist :: FilePath -> IO Bool setFileOrdinary :: FilePath -> IO () setFileExecutable :: FilePath -> IO () -- | The path name that represents the current directory. In Unix, it's -- ".", but this is system-specific. (E.g. AmigaOS uses the -- empty string "" for the current directory.) currentDir :: FilePath shortRelativePath :: FilePath -> FilePath -> FilePath -- | Find a file by looking in a search path. The file path must match -- exactly. findFile :: [FilePath] -> FilePath -> IO FilePath findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a) -- | Find a file by looking in a search path with one of a list of possible -- file extensions. The file base name should be given and it will be -- tried with each of the extensions in each element of the search path. findFileWithExtension :: [String] -> [FilePath] -> FilePath -> IO (Maybe FilePath) -- | Like findFileWithExtension but returns which element of the -- search path the file was found in, and the file path relative to that -- base directory. findFileWithExtension' :: [String] -> [FilePath] -> FilePath -> IO (Maybe (FilePath, FilePath)) -- | Find the file corresponding to a Haskell module name. -- -- This is similar to findFileWithExtension' but specialised to a -- module name. The function fails if the file corresponding to the -- module is missing. findModuleFile :: [FilePath] -> [String] -> ModuleName -> IO (FilePath, FilePath) -- | Finds the files corresponding to a list of Haskell module names. -- -- As findModuleFile but for a list of module names. findModuleFiles :: [FilePath] -> [String] -> [ModuleName] -> IO [(FilePath, FilePath)] -- | List all the files in a directory and all subdirectories. -- -- The order places files in sub-directories after all the files in their -- parent directories. The list is generated lazily so is not well -- defined if the source directory structure changes before the list is -- used. getDirectoryContentsRecursive :: FilePath -> IO [FilePath] -- | Is this directory in the system search path? isInSearchPath :: FilePath -> IO Bool addLibraryPath :: OS -> [FilePath] -> [(String, String)] -> [(String, String)] matchFileGlob :: FilePath -> IO [FilePath] matchDirFileGlob :: FilePath -> FilePath -> IO [FilePath] parseFileGlob :: FilePath -> Maybe FileGlob data FileGlob -- | No glob at all, just an ordinary file [NoGlob] :: FilePath -> FileGlob -- | dir prefix and extension, like "foo/bar/*.baz" corresponds to -- FileGlob "foo/bar" ".baz" [FileGlob] :: FilePath -> String -> FileGlob -- | Compare the modification times of two files to see if the first is -- newer than the second. The first file must exist but the second need -- not. The expected use case is when the second file is generated using -- the first. In this use case, if the result is True then the second -- file is out of date. moreRecentFile :: FilePath -> FilePath -> IO Bool -- | Like moreRecentFile, but also checks that the first file -- exists. existsAndIsMoreRecentThan :: FilePath -> FilePath -> IO Bool -- | Advanced options for withTempFile and withTempDirectory. data TempFileOptions [TempFileOptions] :: Bool -> TempFileOptions -- | Keep temporary files? [optKeepTempFiles] :: TempFileOptions -> Bool defaultTempFileOptions :: TempFileOptions -- | Use a temporary filename that doesn't already exist. withTempFile :: FilePath -> String -> (FilePath -> Handle -> IO a) -> IO a -- | A version of withTempFile that additionally takes a -- TempFileOptions argument. withTempFileEx :: TempFileOptions -> FilePath -> String -> (FilePath -> Handle -> IO a) -> IO a -- | Create and use a temporary directory. -- -- Creates a new temporary directory inside the given directory, making -- use of the template. The temp directory is deleted after use. For -- example: -- --
--   withTempDirectory verbosity "src" "sdist." $ \tmpDir -> do ...
--   
-- -- The tmpDir will be a new subdirectory of the given directory, -- e.g. src/sdist.342. withTempDirectory :: Verbosity -> FilePath -> String -> (FilePath -> IO a) -> IO a -- | A version of withTempDirectory that additionally takes a -- TempFileOptions argument. withTempDirectoryEx :: Verbosity -> TempFileOptions -> FilePath -> String -> (FilePath -> IO a) -> IO a -- | Package description file (pkgname.cabal) defaultPackageDesc :: Verbosity -> IO FilePath -- | Find a package description file in the given directory. Looks for -- .cabal files. findPackageDesc :: FilePath -> IO (Either String FilePath) -- | Like findPackageDesc, but calls die in case of error. tryFindPackageDesc :: FilePath -> IO FilePath -- | Optional auxiliary package information file -- (pkgname.buildinfo) defaultHookedPackageDesc :: IO (Maybe FilePath) -- | Find auxiliary package information in the given directory. Looks for -- .buildinfo files. findHookedPackageDesc :: FilePath -> IO (Maybe FilePath) -- | Gets the contents of a file, but guarantee that it gets closed. -- -- The file is read lazily but if it is not fully consumed by the action -- then the remaining input is truncated and the file is closed. withFileContents :: FilePath -> (String -> IO a) -> IO a -- | Writes a file atomically. -- -- The file is either written successfully or an IO exception is raised -- and the original file is left unchanged. -- -- On windows it is not possible to delete a file that is open by a -- process. This case will give an IO exception but the atomic property -- is not affected. writeFileAtomic :: FilePath -> ByteString -> IO () -- | Write a file but only if it would have new content. If we would be -- writing the same as the existing content then leave the file as is so -- that we do not update the file's modification time. -- -- NB: the file is assumed to be ASCII-encoded. rewriteFile :: FilePath -> String -> IO () fromUTF8 :: String -> String toUTF8 :: String -> String -- | Reads a UTF8 encoded text file as a Unicode String -- -- Reads lazily using ordinary readFile. readUTF8File :: FilePath -> IO String -- | Reads a UTF8 encoded text file as a Unicode String -- -- Same behaviour as withFileContents. withUTF8FileContents :: FilePath -> (String -> IO a) -> IO a -- | Writes a Unicode String as a UTF8 encoded text file. -- -- Uses writeFileAtomic, so provides the same guarantees. writeUTF8File :: FilePath -> String -> IO () -- | Fix different systems silly line ending conventions normaliseLineEndings :: String -> String -- | dropWhileEndLE p is equivalent to reverse . dropWhile p . -- reverse, but quite a bit faster. The difference between -- "Data.List.dropWhileEnd" and this version is that the one in -- Data.List is strict in elements, but spine-lazy, while this one -- is spine-strict but lazy in elements. That's what LE stands -- for - "lazy in elements". -- -- Example: -- --
--   > tail $ Data.List.dropWhileEnd (<3) [undefined, 5, 4, 3, 2, 1]
--   *** Exception: Prelude.undefined
--   > tail $ dropWhileEndLE (<3) [undefined, 5, 4, 3, 2, 1]
--   [5,4,3]
--   > take 3 $ Data.List.dropWhileEnd (<3) [5, 4, 3, 2, 1, undefined]
--   [5,4,3]
--   > take 3 $ dropWhileEndLE (<3) [5, 4, 3, 2, 1, undefined]
--   *** Exception: Prelude.undefined
--   
dropWhileEndLE :: (a -> Bool) -> [a] -> [a] -- | takeWhileEndLE p is equivalent to reverse . takeWhile p . -- reverse, but is usually faster (as well as being easier to read). takeWhileEndLE :: (a -> Bool) -> [a] -> [a] equating :: Eq a => (b -> a) -> b -> b -> Bool comparing :: Ord a => (b -> a) -> b -> b -> Ordering isInfixOf :: String -> String -> Bool -- | intercalate xs xss is equivalent to (concat -- (intersperse xs xss)). It inserts the list xs in -- between the lists in xss and concatenates the result. intercalate :: [a] -> [[a]] -> [a] lowercase :: String -> String -- | Like "Data.List.union", but has O(n log n) complexity instead -- of O(n^2). listUnion :: (Ord a) => [a] -> [a] -> [a] -- | A right-biased version of listUnion. -- -- Example: -- --
--   > listUnion [1,2,3,4,3] [2,1,1]
--   [1,2,3,4,3]
--   > listUnionRight [1,2,3,4,3] [2,1,1]
--   [4,3,2,1,1]
--   
listUnionRight :: (Ord a) => [a] -> [a] -> [a] -- | Like "Data.List.nub", but has O(n log n) complexity instead -- of O(n^2). Code for ordNub and listUnion taken -- from Niklas Hambüchen's ordnub package. ordNub :: (Ord a) => [a] -> [a] -- | A right-biased version of ordNub. -- -- Example: -- --
--   > ordNub [1,2,1]
--   [1,2]
--   > ordNubRight [1,2,1]
--   [2,1]
--   
ordNubRight :: (Ord a) => [a] -> [a] -- | Wraps text to the default line width. Existing newlines are preserved. wrapText :: String -> String -- | Wraps a list of words to a list of lines of words of a particular -- width. wrapLine :: Int -> [String] -> [[String]] -- | This is the information about an installed package that is -- communicated to the ghc-pkg program in order to register a -- package. ghc-pkg now consumes this package format (as of -- version 6.4). This is specific to GHC at the moment. -- -- The .cabal file format is for describing a package that is -- not yet installed. It has a lot of flexibility, like conditionals and -- dependency ranges. As such, that format is not at all suitable for -- describing a package that has already been built and installed. By the -- time we get to that stage, we have resolved all conditionals and -- resolved dependency version constraints to exact versions of dependent -- packages. So, this module defines the InstalledPackageInfo data -- structure that contains all the info we keep about an installed -- package. There is a parser and pretty printer. The textual format is -- rather simpler than the .cabal format: there are no sections, -- for example. module Distribution.InstalledPackageInfo data InstalledPackageInfo_ m [InstalledPackageInfo] :: InstalledPackageId -> PackageId -> PackageKey -> License -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Bool -> [ExposedModule] -> [(m, OriginalModule)] -> [m] -> Bool -> [FilePath] -> [FilePath] -> FilePath -> [String] -> [String] -> [String] -> [FilePath] -> [String] -> [InstalledPackageId] -> [String] -> [String] -> [FilePath] -> [String] -> [FilePath] -> [FilePath] -> Maybe FilePath -> InstalledPackageInfo_ m [installedPackageId] :: InstalledPackageInfo_ m -> InstalledPackageId [sourcePackageId] :: InstalledPackageInfo_ m -> PackageId [packageKey] :: InstalledPackageInfo_ m -> PackageKey [license] :: InstalledPackageInfo_ m -> License [copyright] :: InstalledPackageInfo_ m -> String [maintainer] :: InstalledPackageInfo_ m -> String [author] :: InstalledPackageInfo_ m -> String [stability] :: InstalledPackageInfo_ m -> String [homepage] :: InstalledPackageInfo_ m -> String [pkgUrl] :: InstalledPackageInfo_ m -> String [synopsis] :: InstalledPackageInfo_ m -> String [description] :: InstalledPackageInfo_ m -> String [category] :: InstalledPackageInfo_ m -> String [exposed] :: InstalledPackageInfo_ m -> Bool [exposedModules] :: InstalledPackageInfo_ m -> [ExposedModule] [instantiatedWith] :: InstalledPackageInfo_ m -> [(m, OriginalModule)] [hiddenModules] :: InstalledPackageInfo_ m -> [m] [trusted] :: InstalledPackageInfo_ m -> Bool [importDirs] :: InstalledPackageInfo_ m -> [FilePath] [libraryDirs] :: InstalledPackageInfo_ m -> [FilePath] [dataDir] :: InstalledPackageInfo_ m -> FilePath [hsLibraries] :: InstalledPackageInfo_ m -> [String] [extraLibraries] :: InstalledPackageInfo_ m -> [String] [extraGHCiLibraries] :: InstalledPackageInfo_ m -> [String] [includeDirs] :: InstalledPackageInfo_ m -> [FilePath] [includes] :: InstalledPackageInfo_ m -> [String] [depends] :: InstalledPackageInfo_ m -> [InstalledPackageId] [ccOptions] :: InstalledPackageInfo_ m -> [String] [ldOptions] :: InstalledPackageInfo_ m -> [String] [frameworkDirs] :: InstalledPackageInfo_ m -> [FilePath] [frameworks] :: InstalledPackageInfo_ m -> [String] [haddockInterfaces] :: InstalledPackageInfo_ m -> [FilePath] [haddockHTMLs] :: InstalledPackageInfo_ m -> [FilePath] [pkgRoot] :: InstalledPackageInfo_ m -> Maybe FilePath type InstalledPackageInfo = InstalledPackageInfo_ ModuleName data OriginalModule [OriginalModule] :: InstalledPackageId -> ModuleName -> OriginalModule [originalPackageId] :: OriginalModule -> InstalledPackageId [originalModuleName] :: OriginalModule -> ModuleName data ExposedModule [ExposedModule] :: ModuleName -> Maybe OriginalModule -> Maybe OriginalModule -> ExposedModule [exposedName] :: ExposedModule -> ModuleName [exposedReexport] :: ExposedModule -> Maybe OriginalModule [exposedSignature] :: ExposedModule -> Maybe OriginalModule data ParseResult a [ParseFailed] :: PError -> ParseResult a [ParseOk] :: [PWarning] -> a -> ParseResult a data PError [AmbiguousParse] :: String -> LineNo -> PError [NoParse] :: String -> LineNo -> PError [TabsError] :: LineNo -> PError [FromString] :: String -> (Maybe LineNo) -> PError data PWarning emptyInstalledPackageInfo :: InstalledPackageInfo_ m parseInstalledPackageInfo :: String -> ParseResult InstalledPackageInfo showInstalledPackageInfo :: InstalledPackageInfo -> String showInstalledPackageInfoField :: String -> Maybe (InstalledPackageInfo -> String) showSimpleInstalledPackageInfoField :: String -> Maybe (InstalledPackageInfo -> String) fieldsInstalledPackageInfo :: [FieldDescr InstalledPackageInfo] instance Selector S1_0_33InstalledPackageInfo_ instance Selector S1_0_32InstalledPackageInfo_ instance Selector S1_0_31InstalledPackageInfo_ instance Selector S1_0_30InstalledPackageInfo_ instance Selector S1_0_29InstalledPackageInfo_ instance Selector S1_0_28InstalledPackageInfo_ instance Selector S1_0_27InstalledPackageInfo_ instance Selector S1_0_26InstalledPackageInfo_ instance Selector S1_0_25InstalledPackageInfo_ instance Selector S1_0_24InstalledPackageInfo_ instance Selector S1_0_23InstalledPackageInfo_ instance Selector S1_0_22InstalledPackageInfo_ instance Selector S1_0_21InstalledPackageInfo_ instance Selector S1_0_20InstalledPackageInfo_ instance Selector S1_0_19InstalledPackageInfo_ instance Selector S1_0_18InstalledPackageInfo_ instance Selector S1_0_17InstalledPackageInfo_ instance Selector S1_0_16InstalledPackageInfo_ instance Selector S1_0_15InstalledPackageInfo_ instance Selector S1_0_14InstalledPackageInfo_ instance Selector S1_0_13InstalledPackageInfo_ instance Selector S1_0_12InstalledPackageInfo_ instance Selector S1_0_11InstalledPackageInfo_ instance Selector S1_0_10InstalledPackageInfo_ instance Selector S1_0_9InstalledPackageInfo_ instance Selector S1_0_8InstalledPackageInfo_ instance Selector S1_0_7InstalledPackageInfo_ instance Selector S1_0_6InstalledPackageInfo_ instance Selector S1_0_5InstalledPackageInfo_ instance Selector S1_0_4InstalledPackageInfo_ instance Selector S1_0_3InstalledPackageInfo_ instance Selector S1_0_2InstalledPackageInfo_ instance Selector S1_0_1InstalledPackageInfo_ instance Selector S1_0_0InstalledPackageInfo_ instance Constructor C1_0InstalledPackageInfo_ instance Datatype D1InstalledPackageInfo_ instance Selector S1_0_2ExposedModule instance Selector S1_0_1ExposedModule instance Selector S1_0_0ExposedModule instance Constructor C1_0ExposedModule instance Datatype D1ExposedModule instance Selector S1_0_1OriginalModule instance Selector S1_0_0OriginalModule instance Constructor C1_0OriginalModule instance Datatype D1OriginalModule instance Show m => Show (InstalledPackageInfo_ m) instance Read m => Read (InstalledPackageInfo_ m) instance Generic (InstalledPackageInfo_ m) instance Show ExposedModule instance Read ExposedModule instance Generic ExposedModule instance Show OriginalModule instance Read OriginalModule instance Eq OriginalModule instance Generic OriginalModule instance Binary m => Binary (InstalledPackageInfo_ m) instance Package (InstalledPackageInfo_ str) instance PackageInstalled (InstalledPackageInfo_ str) instance Text OriginalModule instance Text ExposedModule instance Binary OriginalModule instance Binary ExposedModule -- | This is to do with command line handling. The Cabal command line is -- organised into a number of named sub-commands (much like darcs). The -- CommandUI abstraction represents one of these sub-commands, -- with a name, description, a set of flags. Commands can be associated -- with actions and run. It handles some common stuff automatically, like -- the --help and command line completion flags. It is designed -- to allow other tools make derived commands. This feature is used -- heavily in cabal-install. module Distribution.Simple.Command data CommandUI flags [CommandUI] :: String -> String -> (String -> String) -> Maybe (String -> String) -> Maybe (String -> String) -> flags -> (ShowOrParseArgs -> [OptionField flags]) -> CommandUI flags -- | The name of the command as it would be entered on the command line. -- For example "build". [commandName] :: CommandUI flags -> String -- | A short, one line description of the command to use in help texts. [commandSynopsis] :: CommandUI flags -> String -- | A function that maps a program name to a usage summary for this -- command. [commandUsage] :: CommandUI flags -> String -> String -- | Additional explanation of the command to use in help texts. [commandDescription] :: CommandUI flags -> Maybe (String -> String) -- | Post-Usage notes and examples in help texts [commandNotes] :: CommandUI flags -> Maybe (String -> String) -- | Initial / empty flags [commandDefaultFlags] :: CommandUI flags -> flags -- | All the Option fields for this command [commandOptions] :: CommandUI flags -> ShowOrParseArgs -> [OptionField flags] -- | Show flags in the standard long option command line format commandShowOptions :: CommandUI flags -> flags -> [String] data CommandParse flags [CommandHelp] :: (String -> String) -> CommandParse flags [CommandList] :: [String] -> CommandParse flags [CommandErrors] :: [String] -> CommandParse flags [CommandReadyToGo] :: flags -> CommandParse flags -- | Parse a bunch of command line arguments commandParseArgs :: CommandUI flags -> Bool -> [String] -> CommandParse (flags -> flags, [String]) -- | Helper function for creating globalCommand description getNormalCommandDescriptions :: [Command action] -> [(String, String)] helpCommandUI :: CommandUI () data ShowOrParseArgs [ShowArgs] :: ShowOrParseArgs [ParseArgs] :: ShowOrParseArgs -- | Default "usage" documentation text for commands. usageDefault :: String -> String -> String -- | Create "usage" documentation from a list of parameter configurations. usageAlternatives :: String -> [String] -> String -> String -- | Make a Command from standard GetOpt options. mkCommandUI :: String -> String -> [String] -> flags -> (ShowOrParseArgs -> [OptionField flags]) -> CommandUI flags -- | Mark command as hidden. Hidden commands don't show up in the 'progname -- help' or 'progname --help' output. hiddenCommand :: Command action -> Command action data Command action commandAddAction :: CommandUI flags -> (flags -> [String] -> action) -> Command action -- | Utility function, many commands do not accept additional flags. This -- action fails with a helpful error message if the user supplies any -- extra. noExtraFlags :: [String] -> IO () commandsRun :: CommandUI a -> [Command action] -> [String] -> CommandParse (a, CommandParse action) -- | We usually have a data type for storing configuration values, where -- every field stores a configuration option, and the user sets the value -- either via command line flags or a configuration file. An individual -- OptionField models such a field, and we usually build a list of -- options associated to a configuration data type. data OptionField a [OptionField] :: Name -> [OptDescr a] -> OptionField a [optionName] :: OptionField a -> Name [optionDescr] :: OptionField a -> [OptDescr a] type Name = String -- | Create an option taking a single OptDescr. No explicit Name is given -- for the Option, the name is the first LFlag given. option :: SFlags -> LFlags -> Description -> get -> set -> MkOptDescr get set a -> OptionField a -- | Create an option taking several OptDescrs. You will have to give the -- flags and description individually to the OptDescr constructor. multiOption :: Name -> get -> set -> [get -> set -> OptDescr a] -> OptionField a liftOption :: (b -> a) -> (a -> (b -> b)) -> OptionField a -> OptionField b -- | to view as a FieldDescr, we sort the list of interfaces (Req > Bool -- > Choice > Opt) and consider only the first one. viewAsFieldDescr :: OptionField a -> FieldDescr a -- | An OptionField takes one or more OptDescrs, describing the command -- line interface for the field. data OptDescr a [ReqArg] :: Description -> OptFlags -> ArgPlaceHolder -> (ReadE (a -> a)) -> (a -> [String]) -> OptDescr a [OptArg] :: Description -> OptFlags -> ArgPlaceHolder -> (ReadE (a -> a)) -> (a -> a) -> (a -> [Maybe String]) -> OptDescr a [ChoiceOpt] :: [(Description, OptFlags, a -> a, a -> Bool)] -> OptDescr a [BoolOpt] :: Description -> OptFlags -> OptFlags -> (Bool -> a -> a) -> (a -> Maybe Bool) -> OptDescr a type Description = String -- | Short command line option strings type SFlags = [Char] -- | Long command line option strings type LFlags = [String] type OptFlags = (SFlags, LFlags) type ArgPlaceHolder = String type MkOptDescr get set a = SFlags -> LFlags -> Description -> get -> set -> OptDescr a -- | Create a string-valued command line interface. reqArg :: Monoid b => ArgPlaceHolder -> ReadE b -> (b -> [String]) -> MkOptDescr (a -> b) (b -> a -> a) a -- | (String -> a) variant of "reqArg" reqArg' :: Monoid b => ArgPlaceHolder -> (String -> b) -> (b -> [String]) -> MkOptDescr (a -> b) (b -> a -> a) a -- | Create a string-valued command line interface with a default value. optArg :: Monoid b => ArgPlaceHolder -> ReadE b -> b -> (b -> [Maybe String]) -> MkOptDescr (a -> b) (b -> a -> a) a -- | (String -> a) variant of "optArg" optArg' :: Monoid b => ArgPlaceHolder -> (Maybe String -> b) -> (b -> [Maybe String]) -> MkOptDescr (a -> b) (b -> a -> a) a noArg :: (Eq b, Monoid b) => b -> MkOptDescr (a -> b) (b -> a -> a) a boolOpt :: (b -> Maybe Bool) -> (Bool -> b) -> SFlags -> SFlags -> MkOptDescr (a -> b) (b -> a -> a) a boolOpt' :: (b -> Maybe Bool) -> (Bool -> b) -> OptFlags -> OptFlags -> MkOptDescr (a -> b) (b -> a -> a) a -- | create a Choice option choiceOpt :: Eq b => [(b, OptFlags, Description)] -> MkOptDescr (a -> b) (b -> a -> a) a -- | create a Choice option out of an enumeration type. As long flags, the -- Show output is used. As short flags, the first character which does -- not conflict with a previous one is used. choiceOptFromEnum :: (Bounded b, Enum b, Show b, Eq b) => MkOptDescr (a -> b) (b -> a -> a) a instance Functor CommandParse -- | This is about the cabal configurations feature. It exports -- finalizePackageDescription and flattenPackageDescription -- which are functions for converting GenericPackageDescriptions -- down to PackageDescriptions. It has code for working with the -- tree of conditions and resolving or flattening conditions. module Distribution.PackageDescription.Configuration -- | Create a package description with all configurations resolved. -- -- This function takes a GenericPackageDescription and several -- environment parameters and tries to generate PackageDescription -- by finding a flag assignment that result in satisfiable dependencies. -- -- It takes as inputs a not necessarily complete specifications of flags -- assignments, an optional package index as well as platform parameters. -- If some flags are not assigned explicitly, this function will try to -- pick an assignment that causes this function to succeed. The package -- index is optional since on some platforms we cannot determine which -- packages have been installed before. When no package index is -- supplied, every dependency is assumed to be satisfiable, therefore all -- not explicitly assigned flags will get their default values. -- -- This function will fail if it cannot find a flag assignment that leads -- to satisfiable dependencies. (It will not try alternative assignments -- for explicitly specified flags.) In case of failure it will return a -- minimum number of dependencies that could not be satisfied. On -- success, it will return the package description and the full flag -- assignment chosen. finalizePackageDescription :: FlagAssignment -> (Dependency -> Bool) -> Platform -> CompilerInfo -> [Dependency] -> GenericPackageDescription -> Either [Dependency] (PackageDescription, FlagAssignment) -- | Flatten a generic package description by ignoring all conditions and -- just join the field descriptors into on package description. Note, -- however, that this may lead to inconsistent field values, since all -- values are joined into one field, which may not be possible in the -- original package description, due to the use of exclusive choices (if -- ... else ...). -- -- TODO: One particularly tricky case is defaulting. In the original -- package description, e.g., the source directory might either be the -- default or a certain, explicitly set path. Since defaults are filled -- in only after the package has been resolved and when no explicit value -- has been set, the default path will be missing from the package -- description returned by this function. flattenPackageDescription :: GenericPackageDescription -> PackageDescription -- | Parse a configuration condition from a string. parseCondition :: ReadP r (Condition ConfVar) freeVars :: CondTree ConfVar c a -> [FlagName] mapCondTree :: (a -> b) -> (c -> d) -> (Condition v -> Condition w) -> CondTree v c a -> CondTree w d b mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c b mapTreeConds :: (Condition v -> Condition w) -> CondTree v c a -> CondTree w c a mapTreeConstrs :: (c -> d) -> CondTree v c a -> CondTree v d a instance Show PDTagged instance Read DependencyMap instance Show DependencyMap instance Monoid d => Monoid (DepTestRslt d) instance Monoid DependencyMap instance Monoid PDTagged -- | This has code for checking for various problems in packages. There is -- one set of checks that just looks at a PackageDescription in -- isolation and another set of checks that also looks at files in the -- package. Some of the checks are basic sanity checks, others are -- portability standards that we'd like to encourage. There is a -- PackageCheck type that distinguishes the different kinds of -- check so we can see which ones are appropriate to report in different -- situations. This code gets uses when configuring a package when we -- consider only basic problems. The higher standard is uses when when -- preparing a source tarball and by Hackage when uploading new packages. -- The reason for this is that we want to hold packages that are expected -- to be distributed to a higher standard than packages that are only -- ever expected to be used on the author's own environment. module Distribution.PackageDescription.Check -- | Results of some kind of failed package check. -- -- There are a range of severities, from merely dubious to totally -- insane. All of them come with a human readable explanation. In future -- we may augment them with more machine readable explanations, for -- example to help an IDE suggest automatic corrections. data PackageCheck -- | This package description is no good. There's no way it's going to -- build sensibly. This should give an error at configure time. [PackageBuildImpossible] :: String -> PackageCheck [explanation] :: PackageCheck -> String -- | A problem that is likely to affect building the package, or an issue -- that we'd like every package author to be aware of, even if the -- package is never distributed. [PackageBuildWarning] :: String -> PackageCheck [explanation] :: PackageCheck -> String -- | An issue that might not be a problem for the package author but might -- be annoying or detrimental when the package is distributed to users. -- We should encourage distributed packages to be free from these issues, -- but occasionally there are justifiable reasons so we cannot ban them -- entirely. [PackageDistSuspicious] :: String -> PackageCheck [explanation] :: PackageCheck -> String -- | An issue that is OK in the author's environment but is almost certain -- to be a portability problem for other environments. We can quite -- legitimately refuse to publicly distribute packages with these -- problems. [PackageDistInexcusable] :: String -> PackageCheck [explanation] :: PackageCheck -> String -- | Check for common mistakes and problems in package descriptions. -- -- This is the standard collection of checks covering all aspects except -- for checks that require looking at files within the package. For those -- see checkPackageFiles. -- -- It requires the GenericPackageDescription and optionally a -- particular configuration of that package. If you pass Nothing -- then we just check a version of the generic description using -- flattenPackageDescription. checkPackage :: GenericPackageDescription -> Maybe PackageDescription -> [PackageCheck] checkConfiguredPackage :: PackageDescription -> [PackageCheck] -- | Sanity check things that requires IO. It looks at the files in the -- package and expects to find the package unpacked in at the given file -- path. checkPackageFiles :: PackageDescription -> FilePath -> IO [PackageCheck] -- | Sanity check things that requires looking at files in the package. -- This is a generalised version of checkPackageFiles that can -- work in any monad for which you can provide -- CheckPackageContentOps operations. -- -- The point of this extra generality is to allow doing checks in some -- virtual file system, for example a tarball in memory. checkPackageContent :: Monad m => CheckPackageContentOps m -> PackageDescription -> m [PackageCheck] -- | A record of operations needed to check the contents of packages. Used -- by checkPackageContent. data CheckPackageContentOps m [CheckPackageContentOps] :: (FilePath -> m Bool) -> (FilePath -> m Bool) -> CheckPackageContentOps m [doesFileExist] :: CheckPackageContentOps m -> FilePath -> m Bool [doesDirectoryExist] :: CheckPackageContentOps m -> FilePath -> m Bool -- | Check the names of all files in a package for portability problems. -- This should be done for example when creating or validating a package -- tarball. checkPackageFileNames :: [FilePath] -> [PackageCheck] instance Eq PackageCheck instance Show PackageCheck -- | This defined parsers and partial pretty printers for the -- .cabal format. Some of the complexity in this module is due -- to the fact that we have to be backwards compatible with old -- .cabal files, so there's code to translate into the newer -- structure. module Distribution.PackageDescription.Parse -- | Parse the given package file. readPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescription writePackageDescription :: FilePath -> PackageDescription -> IO () -- | Parses the given file into a GenericPackageDescription. -- -- In Cabal 1.2 the syntax for package descriptions was changed to a -- format with sections and possibly indented property descriptions. parsePackageDescription :: String -> ParseResult GenericPackageDescription showPackageDescription :: PackageDescription -> String data ParseResult a [ParseFailed] :: PError -> ParseResult a [ParseOk] :: [PWarning] -> a -> ParseResult a -- | Field descriptor. The parameter a parameterizes over where -- the field's value is stored in. data FieldDescr a [FieldDescr] :: String -> (a -> Doc) -> (LineNo -> String -> a -> ParseResult a) -> FieldDescr a [fieldName] :: FieldDescr a -> String [fieldGet] :: FieldDescr a -> a -> Doc -- | fieldSet n str x Parses the field value from the given input -- string str and stores the result in x if the parse -- was successful. Otherwise, reports an error on line number n. [fieldSet] :: FieldDescr a -> LineNo -> String -> a -> ParseResult a type LineNo = Int readHookedBuildInfo :: Verbosity -> FilePath -> IO HookedBuildInfo parseHookedBuildInfo :: String -> ParseResult HookedBuildInfo writeHookedBuildInfo :: FilePath -> HookedBuildInfo -> IO () showHookedBuildInfo :: HookedBuildInfo -> String pkgDescrFieldDescrs :: [FieldDescr PackageDescription] libFieldDescrs :: [FieldDescr Library] executableFieldDescrs :: [FieldDescr Executable] binfoFieldDescrs :: [FieldDescr BuildInfo] sourceRepoFieldDescrs :: [FieldDescr SourceRepo] testSuiteFieldDescrs :: [FieldDescr TestSuiteStanza] flagFieldDescrs :: [FieldDescr Flag] instance Data DependencyWithRenaming instance Eq DependencyWithRenaming instance Show DependencyWithRenaming instance Read DependencyWithRenaming instance Functor f => Functor (StT s f) instance (Monad m, Functor m) => Applicative (StT s m) instance Monad m => Monad (StT s m) instance Text DependencyWithRenaming -- | Pretty printing for cabal files module Distribution.PackageDescription.PrettyPrint -- | Writes a .cabal file from a generic package description writeGenericPackageDescription :: FilePath -> GenericPackageDescription -> IO () -- | Writes a generic package description to a string showGenericPackageDescription :: GenericPackageDescription -> String module Distribution.Utils.NubList -- | NubList : A de-duplicated list that maintains the original order. data NubList a -- | Smart constructor for the NubList type. toNubList :: Ord a => [a] -> NubList a fromNubList :: NubList a -> [a] -- | Lift a function over lists to a function over NubLists. overNubList :: Ord a => ([a] -> [a]) -> NubList a -> NubList a -- | NubListR : A right-biased version of NubList. That is -- toNubListR ["-XNoFoo", "-XFoo", "-XNoFoo"] will result in -- ["-XFoo", "-XNoFoo"], unlike the normal NubList, which -- is left-biased. Built on top of ordNubRight and -- listUnionRight. data NubListR a -- | Smart constructor for the NubListR type. toNubListR :: Ord a => [a] -> NubListR a fromNubListR :: NubListR a -> [a] -- | Lift a function over lists to a function over NubListRs. overNubListR :: Ord a => ([a] -> [a]) -> NubListR a -> NubListR a instance Eq a => Eq (NubListR a) instance Eq a => Eq (NubList a) instance Ord a => Monoid (NubList a) instance Show a => Show (NubList a) instance (Ord a, Read a) => Read (NubList a) instance (Ord a, Binary a) => Binary (NubList a) instance Ord a => Monoid (NubListR a) instance Show a => Show (NubListR a) instance (Ord a, Read a) => Read (NubListR a) -- | An index of packages. module Distribution.Simple.PackageIndex -- | The default package index which contains InstalledPackageInfo. -- Normally use this. type InstalledPackageIndex = PackageIndex InstalledPackageInfo -- | The collection of information about packages from one or more -- PackageDBs. These packages generally should have an instance -- of PackageInstalled -- -- Packages are uniquely identified in by their -- InstalledPackageId, they can also be efficiently looked up by -- package name or by name and version. data PackageIndex a -- | Map from fake installed package IDs to real ones. See Note [FakeMap] type FakeMap = Map InstalledPackageId InstalledPackageId -- | Build an index out of a bunch of packages. -- -- If there are duplicates by InstalledPackageId then later ones -- mask earlier ones. fromList :: PackageInstalled a => [a] -> PackageIndex a -- | Merge two indexes. -- -- Packages from the second mask packages from the first if they have the -- exact same InstalledPackageId. -- -- For packages with the same source PackageId, packages from the -- second are "preferred" over those from the first. Being preferred -- means they are top result when we do a lookup by source -- PackageId. This is the mechanism we use to prefer user packages -- over global packages. merge :: PackageInstalled a => PackageIndex a -> PackageIndex a -> PackageIndex a -- | Inserts a single package into the index. -- -- This is equivalent to (but slightly quicker than) using mappend -- or merge with a singleton index. insert :: PackageInstalled a => a -> PackageIndex a -> PackageIndex a -- | Removes a single installed package from the index. deleteInstalledPackageId :: PackageInstalled a => InstalledPackageId -> PackageIndex a -> PackageIndex a -- | Removes all packages with this source PackageId from the index. deleteSourcePackageId :: PackageInstalled a => PackageId -> PackageIndex a -> PackageIndex a -- | Removes all packages with this (case-sensitive) name from the index. deletePackageName :: PackageInstalled a => PackageName -> PackageIndex a -> PackageIndex a -- | Does a lookup by source package id (name & version). -- -- Since multiple package DBs mask each other by -- InstalledPackageId, then we get back at most one package. lookupInstalledPackageId :: PackageInstalled a => PackageIndex a -> InstalledPackageId -> Maybe a -- | Does a lookup by source package id (name & version). -- -- There can be multiple installed packages with the same source -- PackageId but different InstalledPackageId. They are -- returned in order of preference, with the most preferred first. lookupSourcePackageId :: PackageInstalled a => PackageIndex a -> PackageId -> [a] -- | Convenient alias of lookupSourcePackageId, but assuming only -- one package per package ID. lookupPackageId :: PackageInstalled a => PackageIndex a -> PackageId -> Maybe a -- | Does a lookup by source package name. lookupPackageName :: PackageInstalled a => PackageIndex a -> PackageName -> [(Version, [a])] -- | Does a lookup by source package name and a range of versions. -- -- We get back any number of versions of the specified package name, all -- satisfying the version range constraint. lookupDependency :: PackageInstalled a => PackageIndex a -> Dependency -> [(Version, [a])] -- | Does a case-insensitive search by package name. -- -- If there is only one package that compares case-insensitively to this -- name then the search is unambiguous and we get back all versions of -- that package. If several match case-insensitively but one matches -- exactly then it is also unambiguous. -- -- If however several match case-insensitively and none match exactly -- then we have an ambiguous result, and we get back all the versions of -- all the packages. The list of ambiguous results is split by exact -- package name. So it is a non-empty list of non-empty lists. searchByName :: PackageInstalled a => PackageIndex a -> String -> SearchResult [a] data SearchResult a [None] :: SearchResult a [Unambiguous] :: a -> SearchResult a [Ambiguous] :: [a] -> SearchResult a -- | Does a case-insensitive substring search by package name. -- -- That is, all packages that contain the given string in their name. searchByNameSubstring :: PackageInstalled a => PackageIndex a -> String -> [a] -- | Get all the packages from the index. allPackages :: PackageIndex a -> [a] -- | Get all the packages from the index. -- -- They are grouped by package name (case-sensitively). allPackagesByName :: PackageIndex a -> [(PackageName, [a])] -- | Get all the packages from the index. -- -- They are grouped by source package id (package name and version). allPackagesBySourcePackageId :: PackageInstalled a => PackageIndex a -> [(PackageId, [a])] -- | All packages that have immediate dependencies that are not in the -- index. -- -- Returns such packages along with the dependencies that they're -- missing. brokenPackages :: PackageInstalled a => PackageIndex a -> [(a, [InstalledPackageId])] -- | Tries to take the transitive closure of the package dependencies. -- -- If the transitive closure is complete then it returns that subset of -- the index. Otherwise it returns the broken packages as in -- brokenPackages. -- -- dependencyClosure :: PackageInstalled a => PackageIndex a -> [InstalledPackageId] -> Either (PackageIndex a) [(a, [InstalledPackageId])] -- | Takes the transitive closure of the packages reverse dependencies. -- -- reverseDependencyClosure :: PackageInstalled a => PackageIndex a -> [InstalledPackageId] -> [a] topologicalOrder :: PackageInstalled a => PackageIndex a -> [a] reverseTopologicalOrder :: PackageInstalled a => PackageIndex a -> [a] -- | Given a package index where we assume we want to use all the packages -- (use dependencyClosure if you need to get such a index subset) -- find out if the dependencies within it use consistent versions of each -- package. Return all cases where multiple packages depend on different -- versions of some other package. -- -- Each element in the result is a package name along with the packages -- that depend on it and the versions they require. These are guaranteed -- to be distinct. dependencyInconsistencies :: PackageInstalled a => PackageIndex a -> [(PackageName, [(PackageId, Version)])] -- | Find if there are any cycles in the dependency graph. If there are no -- cycles the result is []. -- -- This actually computes the strongly connected components. So it gives -- us a list of groups of packages where within each group they all -- depend on each other, directly or indirectly. dependencyCycles :: PackageInstalled a => PackageIndex a -> [[a]] -- | Builds a graph of the package dependencies. -- -- Dependencies on other packages that are not in the index are -- discarded. You can check if there are any such dependencies with -- brokenPackages. dependencyGraph :: PackageInstalled a => PackageIndex a -> (Graph, Vertex -> a, InstalledPackageId -> Maybe Vertex) -- | A rough approximation of GHC's module finder, takes a -- InstalledPackageIndex and turns it into a map from module names -- to their source packages. It's used to initialize the -- build-deps field in cabal init. moduleNameIndex :: InstalledPackageIndex -> Map ModuleName [InstalledPackageInfo] -- | Variant of lookupInstalledPackageId which accepts a -- FakeMap. See Note [FakeMap]. fakeLookupInstalledPackageId :: PackageInstalled a => FakeMap -> PackageIndex a -> InstalledPackageId -> Maybe a -- | Variant of brokenPackages which accepts a FakeMap. See -- Note [FakeMap]. brokenPackages' :: PackageInstalled a => FakeMap -> PackageIndex a -> [(a, [InstalledPackageId])] -- | Variant of dependencyClosure which accepts a FakeMap. -- See Note [FakeMap]. dependencyClosure' :: PackageInstalled a => FakeMap -> PackageIndex a -> [InstalledPackageId] -> Either (PackageIndex a) [(a, [InstalledPackageId])] -- | Variant of reverseDependencyClosure which accepts a -- FakeMap. See Note [FakeMap]. reverseDependencyClosure' :: PackageInstalled a => FakeMap -> PackageIndex a -> [InstalledPackageId] -> [a] -- | Variant of dependencyInconsistencies which accepts a -- FakeMap. See Note [FakeMap]. dependencyInconsistencies' :: PackageInstalled a => FakeMap -> PackageIndex a -> [(PackageName, [(PackageId, Version)])] -- | Variant of dependencyCycles which accepts a FakeMap. See -- Note [FakeMap]. dependencyCycles' :: PackageInstalled a => FakeMap -> PackageIndex a -> [[a]] -- | Variant of dependencyGraph which accepts a FakeMap. See -- Note [FakeMap]. dependencyGraph' :: PackageInstalled a => FakeMap -> PackageIndex a -> (Graph, Vertex -> a, InstalledPackageId -> Maybe Vertex) instance Constructor C1_0PackageIndex instance Datatype D1PackageIndex instance Read a => Read (PackageIndex a) instance Show a => Show (PackageIndex a) instance Generic (PackageIndex a) instance Binary a => Binary (PackageIndex a) instance PackageInstalled a => Monoid (PackageIndex a) -- | A somewhat extended notion of the normal program search path concept. -- -- Usually when finding executables we just want to look in the usual -- places using the OS's usual method for doing so. In Haskell the normal -- OS-specific method is captured by findExecutable. On all common -- OSs that makes use of a PATH environment variable, (though on -- Windows it is not just the PATH). -- -- However it is sometimes useful to be able to look in additional -- locations without having to change the process-global PATH -- environment variable. So we need an extension of the usual -- findExecutable that can look in additional locations, either -- before, after or instead of the normal OS locations. module Distribution.Simple.Program.Find -- | A search path to use when locating executables. This is analogous to -- the unix $PATH or win32 %PATH% but with the ability -- to use the system default method for finding executables -- (findExecutable which on unix is simply looking on the -- $PATH but on win32 is a bit more complicated). -- -- The default to use is [ProgSearchPathDefault] but you can add -- extra dirs either before, after or instead of the default, e.g. here -- we add an extra dir to search after the usual ones. -- --
--   ['ProgramSearchPathDefault', 'ProgramSearchPathDir' dir]
--   
type ProgramSearchPath = [ProgramSearchPathEntry] data ProgramSearchPathEntry -- | A specific dir [ProgramSearchPathDir] :: FilePath -> ProgramSearchPathEntry -- | The system default [ProgramSearchPathDefault] :: ProgramSearchPathEntry defaultProgramSearchPath :: ProgramSearchPath findProgramOnSearchPath :: Verbosity -> ProgramSearchPath -> FilePath -> IO (Maybe FilePath) -- | Interpret a ProgramSearchPath to construct a new $PATH -- env var. Note that this is close but not perfect because on Windows -- the search algorithm looks at more than just the %PATH%. programSearchPathAsPATHVar :: ProgramSearchPath -> IO String -- | This provides an abstraction which deals with configuring and running -- programs. A Program is a static notion of a known program. A -- ConfiguredProgram is a Program that has been found on -- the current machine and is ready to be run (possibly with some -- user-supplied default args). Configuring a program involves finding -- its location and if necessary finding its version. There's reasonable -- default behavior for trying to find "foo" in PATH, being able to -- override its location, etc. module Distribution.Simple.Program.Types -- | Represents a program which can be configured. -- -- Note: rather than constructing this directly, start with -- simpleProgram and override any extra fields. data Program [Program] :: String -> (Verbosity -> ProgramSearchPath -> IO (Maybe FilePath)) -> (Verbosity -> FilePath -> IO (Maybe Version)) -> (Verbosity -> ConfiguredProgram -> IO ConfiguredProgram) -> Program -- | The simple name of the program, eg. ghc [programName] :: Program -> String -- | A function to search for the program if its location was not specified -- by the user. Usually this will just be a call to -- findProgramOnSearchPath. -- -- It is supplied with the prevailing search path which will typically -- just be used as-is, but can be extended or ignored as needed. [programFindLocation] :: Program -> Verbosity -> ProgramSearchPath -> IO (Maybe FilePath) -- | Try to find the version of the program. For many programs this is not -- possible or is not necessary so it's OK to return Nothing. [programFindVersion] :: Program -> Verbosity -> FilePath -> IO (Maybe Version) -- | A function to do any additional configuration after we have located -- the program (and perhaps identified its version). For example it could -- add args, or environment vars. [programPostConf] :: Program -> Verbosity -> ConfiguredProgram -> IO ConfiguredProgram -- | A search path to use when locating executables. This is analogous to -- the unix $PATH or win32 %PATH% but with the ability -- to use the system default method for finding executables -- (findExecutable which on unix is simply looking on the -- $PATH but on win32 is a bit more complicated). -- -- The default to use is [ProgSearchPathDefault] but you can add -- extra dirs either before, after or instead of the default, e.g. here -- we add an extra dir to search after the usual ones. -- --
--   ['ProgramSearchPathDefault', 'ProgramSearchPathDir' dir]
--   
type ProgramSearchPath = [ProgramSearchPathEntry] data ProgramSearchPathEntry -- | A specific dir [ProgramSearchPathDir] :: FilePath -> ProgramSearchPathEntry -- | The system default [ProgramSearchPathDefault] :: ProgramSearchPathEntry -- | Make a simple named program. -- -- By default we'll just search for it in the path and not try to find -- the version name. You can override these behaviours if necessary, eg: -- --
--   simpleProgram "foo" { programFindLocation = ... , programFindVersion ... }
--   
simpleProgram :: String -> Program -- | Represents a program which has been configured and is thus ready to be -- run. -- -- These are usually made by configuring a Program, but if you -- have to construct one directly then start with -- simpleConfiguredProgram and override any extra fields. data ConfiguredProgram [ConfiguredProgram] :: String -> Maybe Version -> [String] -> [String] -> [(String, Maybe String)] -> Map String String -> ProgramLocation -> ConfiguredProgram -- | Just the name again [programId] :: ConfiguredProgram -> String -- | The version of this program, if it is known. [programVersion] :: ConfiguredProgram -> Maybe Version -- | Default command-line args for this program. These flags will appear -- first on the command line, so they can be overridden by subsequent -- flags. [programDefaultArgs] :: ConfiguredProgram -> [String] -- | Override command-line args for this program. These flags will appear -- last on the command line, so they override all earlier flags. [programOverrideArgs] :: ConfiguredProgram -> [String] -- | Override environment variables for this program. These env vars will -- extend/override the prevailing environment of the current to form the -- environment for the new process. [programOverrideEnv] :: ConfiguredProgram -> [(String, Maybe String)] -- | A key-value map listing various properties of the program, useful for -- feature detection. Populated during the configuration step, key names -- depend on the specific program. [programProperties] :: ConfiguredProgram -> Map String String -- | Location of the program. eg. /usr/bin/ghc-6.4 [programLocation] :: ConfiguredProgram -> ProgramLocation -- | The full path of a configured program. programPath :: ConfiguredProgram -> FilePath -- | Suppress any extra arguments added by the user. suppressOverrideArgs :: ConfiguredProgram -> ConfiguredProgram type ProgArg = String -- | Where a program was found. Also tells us whether it's specified by -- user or not. This includes not just the path, but the program as well. data ProgramLocation -- | The user gave the path to this program, eg. -- --ghc-path=/usr/bin/ghc-6.6 [UserSpecified] :: FilePath -> ProgramLocation [locationPath] :: ProgramLocation -> FilePath -- | The program was found automatically. [FoundOnSystem] :: FilePath -> ProgramLocation [locationPath] :: ProgramLocation -> FilePath -- | Make a simple ConfiguredProgram. -- --
--   simpleConfiguredProgram "foo" (FoundOnSystem path)
--   
simpleConfiguredProgram :: String -> ProgramLocation -> ConfiguredProgram instance Selector S1_0_6ConfiguredProgram instance Selector S1_0_5ConfiguredProgram instance Selector S1_0_4ConfiguredProgram instance Selector S1_0_3ConfiguredProgram instance Selector S1_0_2ConfiguredProgram instance Selector S1_0_1ConfiguredProgram instance Selector S1_0_0ConfiguredProgram instance Constructor C1_0ConfiguredProgram instance Datatype D1ConfiguredProgram instance Selector S1_1_0ProgramLocation instance Selector S1_0_0ProgramLocation instance Constructor C1_1ProgramLocation instance Constructor C1_0ProgramLocation instance Datatype D1ProgramLocation instance Show ConfiguredProgram instance Read ConfiguredProgram instance Generic ConfiguredProgram instance Eq ConfiguredProgram instance Show ProgramLocation instance Read ProgramLocation instance Generic ProgramLocation instance Eq ProgramLocation instance Binary ConfiguredProgram instance Binary ProgramLocation -- | This module provides a data type for program invocations and functions -- to run them. module Distribution.Simple.Program.Run -- | Represents a specific invocation of a specific program. -- -- This is used as an intermediate type between deciding how to call a -- program and actually doing it. This provides the opportunity to the -- caller to adjust how the program will be called. These invocations can -- either be run directly or turned into shell or batch scripts. data ProgramInvocation [ProgramInvocation] :: FilePath -> [String] -> [(String, Maybe String)] -> Maybe FilePath -> Maybe String -> IOEncoding -> IOEncoding -> ProgramInvocation [progInvokePath] :: ProgramInvocation -> FilePath [progInvokeArgs] :: ProgramInvocation -> [String] [progInvokeEnv] :: ProgramInvocation -> [(String, Maybe String)] [progInvokeCwd] :: ProgramInvocation -> Maybe FilePath [progInvokeInput] :: ProgramInvocation -> Maybe String [progInvokeInputEncoding] :: ProgramInvocation -> IOEncoding [progInvokeOutputEncoding] :: ProgramInvocation -> IOEncoding data IOEncoding [IOEncodingText] :: IOEncoding [IOEncodingUTF8] :: IOEncoding emptyProgramInvocation :: ProgramInvocation simpleProgramInvocation :: FilePath -> [String] -> ProgramInvocation programInvocation :: ConfiguredProgram -> [String] -> ProgramInvocation -- | Like the unix xargs program. Useful for when we've got very long -- command lines that might overflow an OS limit on command line length -- and so you need to invoke a command multiple times to get all the args -- in. -- -- It takes four template invocations corresponding to the simple, -- initial, middle and last invocations. If the number of args given is -- small enough that we can get away with just a single invocation then -- the simple one is used: -- --
--   $ simple args
--   
-- -- If the number of args given means that we need to use multiple -- invocations then the templates for the initial, middle and last -- invocations are used: -- --
--   $ initial args_0
--   $ middle  args_1
--   $ middle  args_2
--     ...
--   $ final   args_n
--   
multiStageProgramInvocation :: ProgramInvocation -> (ProgramInvocation, ProgramInvocation, ProgramInvocation) -> [String] -> [ProgramInvocation] runProgramInvocation :: Verbosity -> ProgramInvocation -> IO () getProgramInvocationOutput :: Verbosity -> ProgramInvocation -> IO String -- | Return the current environment extended with the given overrides. getEffectiveEnvironment :: [(String, Maybe String)] -> IO (Maybe [(String, String)]) -- | This module provides an library interface to the hc-pkg -- program. Currently only GHC, GHCJS and LHC have hc-pkg programs. module Distribution.Simple.Program.HcPkg -- | Information about the features and capabilities of an hc-pkg -- program. data HcPkgInfo [HcPkgInfo] :: ConfiguredProgram -> Bool -> Bool -> Bool -> Bool -> HcPkgInfo [hcPkgProgram] :: HcPkgInfo -> ConfiguredProgram -- | no package DB stack supported [noPkgDbStack] :: HcPkgInfo -> Bool -- | hc-pkg does not support verbosity flags [noVerboseFlag] :: HcPkgInfo -> Bool -- | use package-conf option instead of package-db [flagPackageConf] :: HcPkgInfo -> Bool -- | requires single file package database [useSingleFileDb] :: HcPkgInfo -> Bool -- | Call hc-pkg to initialise a package database at the location -- {path}. -- --
--   hc-pkg init {path}
--   
init :: HcPkgInfo -> Verbosity -> FilePath -> IO () -- | Run hc-pkg using a given package DB stack, directly -- forwarding the provided command-line arguments to it. invoke :: HcPkgInfo -> Verbosity -> PackageDBStack -> [String] -> IO () -- | Call hc-pkg to register a package. -- --
--   hc-pkg register {filename | -} [--user | --global | --package-db]
--   
register :: HcPkgInfo -> Verbosity -> PackageDBStack -> Either FilePath InstalledPackageInfo -> IO () -- | Call hc-pkg to re-register a package. -- --
--   hc-pkg register {filename | -} [--user | --global | --package-db]
--   
reregister :: HcPkgInfo -> Verbosity -> PackageDBStack -> Either FilePath InstalledPackageInfo -> IO () -- | Call hc-pkg to unregister a package -- --
--   hc-pkg unregister [pkgid] [--user | --global | --package-db]
--   
unregister :: HcPkgInfo -> Verbosity -> PackageDB -> PackageId -> IO () -- | Call hc-pkg to expose a package. -- --
--   hc-pkg expose [pkgid] [--user | --global | --package-db]
--   
expose :: HcPkgInfo -> Verbosity -> PackageDB -> PackageId -> IO () -- | Call hc-pkg to hide a package. -- --
--   hc-pkg hide [pkgid] [--user | --global | --package-db]
--   
hide :: HcPkgInfo -> Verbosity -> PackageDB -> PackageId -> IO () -- | Call hc-pkg to get all the details of all the packages in the -- given package database. dump :: HcPkgInfo -> Verbosity -> PackageDB -> IO [InstalledPackageInfo] -- | Call hc-pkg to get the source package Id of all the packages -- in the given package database. -- -- This is much less information than with dump, but also rather -- quicker. Note in particular that it does not include the -- InstalledPackageId, just the source PackageId which is -- not necessarily unique in any package db. list :: HcPkgInfo -> Verbosity -> PackageDB -> IO [PackageId] initInvocation :: HcPkgInfo -> Verbosity -> FilePath -> ProgramInvocation registerInvocation :: HcPkgInfo -> Verbosity -> PackageDBStack -> Either FilePath InstalledPackageInfo -> ProgramInvocation reregisterInvocation :: HcPkgInfo -> Verbosity -> PackageDBStack -> Either FilePath InstalledPackageInfo -> ProgramInvocation unregisterInvocation :: HcPkgInfo -> Verbosity -> PackageDB -> PackageId -> ProgramInvocation exposeInvocation :: HcPkgInfo -> Verbosity -> PackageDB -> PackageId -> ProgramInvocation hideInvocation :: HcPkgInfo -> Verbosity -> PackageDB -> PackageId -> ProgramInvocation dumpInvocation :: HcPkgInfo -> Verbosity -> PackageDB -> ProgramInvocation listInvocation :: HcPkgInfo -> Verbosity -> PackageDB -> ProgramInvocation -- | This module provides an library interface to the ld linker -- program. module Distribution.Simple.Program.Ld -- | Call ld -r to link a bunch of object files together. combineObjectFiles :: Verbosity -> ConfiguredProgram -> FilePath -> [FilePath] -> IO () -- | This module provides an library interface to the hpc program. module Distribution.Simple.Program.Hpc -- | Invoke hpc with the given parameters. -- -- Prior to HPC version 0.7 (packaged with GHC 7.8), hpc did not handle -- multiple .mix paths correctly, so we print a warning, and only pass it -- the first path in the list. This means that e.g. test suites that -- import their library as a dependency can still work, but those that -- include the library modules directly (in other-modules) don't. markup :: ConfiguredProgram -> Version -> Verbosity -> FilePath -> [FilePath] -> FilePath -> [ModuleName] -> IO () union :: ConfiguredProgram -> Verbosity -> [FilePath] -> FilePath -> [ModuleName] -> IO () -- | This module provides an library interface to the hc-pkg -- program. Currently only GHC and LHC have hc-pkg programs. module Distribution.Simple.Program.Script -- | Generate a system script, either POSIX shell script or Windows batch -- file as appropriate for the given system. invocationAsSystemScript :: OS -> ProgramInvocation -> String -- | Generate a POSIX shell script that invokes a program. invocationAsShellScript :: ProgramInvocation -> String -- | Generate a Windows batch file that invokes a program. invocationAsBatchFile :: ProgramInvocation -> String -- | The module defines all the known built-in Programs. -- -- Where possible we try to find their version numbers. module Distribution.Simple.Program.Builtin -- | The default list of programs. These programs are typically used -- internally to Cabal. builtinPrograms :: [Program] ghcProgram :: Program ghcPkgProgram :: Program ghcjsProgram :: Program ghcjsPkgProgram :: Program lhcProgram :: Program lhcPkgProgram :: Program hmakeProgram :: Program jhcProgram :: Program haskellSuiteProgram :: Program haskellSuitePkgProgram :: Program uhcProgram :: Program gccProgram :: Program arProgram :: Program stripProgram :: Program happyProgram :: Program alexProgram :: Program hsc2hsProgram :: Program c2hsProgram :: Program cpphsProgram :: Program hscolourProgram :: Program haddockProgram :: Program greencardProgram :: Program ldProgram :: Program tarProgram :: Program cppProgram :: Program pkgConfigProgram :: Program hpcProgram :: Program -- | This provides a ProgramDb type which holds configured and -- not-yet configured programs. It is the parameter to lots of actions -- elsewhere in Cabal that need to look up and run programs. If we had a -- Cabal monad, the ProgramDb would probably be a reader or state -- component of it. -- -- One nice thing about using it is that any program that is registered -- with Cabal will get some "configure" and ".cabal" helpers like -- --with-foo-args --foo-path= and extra-foo-args. -- -- There's also a hook for adding programs in a Setup.lhs script. See -- hookedPrograms in UserHooks. This gives a hook user the ability -- to get the above flags and such so that they don't have to write all -- the PATH logic inside Setup.lhs. module Distribution.Simple.Program.Db -- | The configuration is a collection of information about programs. It -- contains information both about configured programs and also about -- programs that we are yet to configure. -- -- The idea is that we start from a collection of unconfigured programs -- and one by one we try to configure them at which point we move them -- into the configured collection. For unconfigured programs we record -- not just the Program but also any user-provided arguments and -- location for the program. data ProgramDb emptyProgramDb :: ProgramDb defaultProgramDb :: ProgramDb -- | The Read/Show instance does not preserve all the unconfigured -- Programs because Program is not in Read/Show because -- it contains functions. So to fully restore a deserialised -- ProgramDb use this function to add back all the known -- Programs. -- -- restoreProgramDb :: [Program] -> ProgramDb -> ProgramDb -- | Add a known program that we may configure later addKnownProgram :: Program -> ProgramDb -> ProgramDb addKnownPrograms :: [Program] -> ProgramDb -> ProgramDb lookupKnownProgram :: String -> ProgramDb -> Maybe Program knownPrograms :: ProgramDb -> [(Program, Maybe ConfiguredProgram)] -- | Get the current ProgramSearchPath used by the ProgramDb. -- This is the default list of locations where programs are looked for -- when configuring them. This can be overridden for specific programs -- (with userSpecifyPath), and specific known programs can modify -- or ignore this search path in their own configuration code. getProgramSearchPath :: ProgramDb -> ProgramSearchPath -- | Change the current ProgramSearchPath used by the -- ProgramDb. This will affect programs that are configured from -- here on, so you should usually set it before configuring any programs. setProgramSearchPath :: ProgramSearchPath -> ProgramDb -> ProgramDb -- | Modify the current ProgramSearchPath used by the -- ProgramDb. This will affect programs that are configured from -- here on, so you should usually modify it before configuring any -- programs. modifyProgramSearchPath :: (ProgramSearchPath -> ProgramSearchPath) -> ProgramDb -> ProgramDb -- | User-specify this path. Basically override any path information for -- this program in the configuration. If it's not a known program ignore -- it. userSpecifyPath :: String -> FilePath -> ProgramDb -> ProgramDb -- | Like userSpecifyPath but for a list of progs and their paths. userSpecifyPaths :: [(String, FilePath)] -> ProgramDb -> ProgramDb userMaybeSpecifyPath :: String -> Maybe FilePath -> ProgramDb -> ProgramDb -- | User-specify the arguments for this program. Basically override any -- args information for this program in the configuration. If it's not a -- known program, ignore it.. userSpecifyArgs :: String -> [ProgArg] -> ProgramDb -> ProgramDb -- | Like userSpecifyPath but for a list of progs and their args. userSpecifyArgss :: [(String, [ProgArg])] -> ProgramDb -> ProgramDb -- | Get any extra args that have been previously specified for a program. userSpecifiedArgs :: Program -> ProgramDb -> [ProgArg] -- | Try to find a configured program lookupProgram :: Program -> ProgramDb -> Maybe ConfiguredProgram -- | Update a configured program in the database. updateProgram :: ConfiguredProgram -> ProgramDb -> ProgramDb -- | List all configured programs. configuredPrograms :: ProgramDb -> [ConfiguredProgram] -- | Try to configure a specific program. If the program is already -- included in the collection of unconfigured programs then we use any -- user-supplied location and arguments. If the program gets configured -- successfully it gets added to the configured collection. -- -- Note that it is not a failure if the program cannot be configured. -- It's only a failure if the user supplied a location and the program -- could not be found at that location. -- -- The reason for it not being a failure at this stage is that we don't -- know up front all the programs we will need, so we try to configure -- them all. To verify that a program was actually successfully -- configured use requireProgram. configureProgram :: Verbosity -> Program -> ProgramDb -> IO ProgramDb -- | Try to configure all the known programs that have not yet been -- configured. configureAllKnownPrograms :: Verbosity -> ProgramDb -> IO ProgramDb -- | Check that a program is configured and available to be run. -- -- Additionally check that the program version number is suitable and -- return it. For example you could require AnyVersion or -- orLaterVersion (Version [1,0] []) -- -- It returns the configured program, its version number and a possibly -- updated ProgramDb. If the program could not be configured or -- the version is unsuitable, it returns an error value. lookupProgramVersion :: Verbosity -> Program -> VersionRange -> ProgramDb -> IO (Either String (ConfiguredProgram, Version, ProgramDb)) -- | reconfigure a bunch of programs given new user-specified args. It -- takes the same inputs as userSpecifyPath and -- userSpecifyArgs and for all progs with a new path it calls -- configureProgram. reconfigurePrograms :: Verbosity -> [(String, FilePath)] -> [(String, [ProgArg])] -> ProgramDb -> IO ProgramDb -- | Check that a program is configured and available to be run. -- -- It raises an exception if the program could not be configured, -- otherwise it returns the configured program. requireProgram :: Verbosity -> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb) -- | Like lookupProgramVersion, but raises an exception in case of -- error instead of returning 'Left errMsg'. requireProgramVersion :: Verbosity -> Program -> VersionRange -> ProgramDb -> IO (ConfiguredProgram, Version, ProgramDb) instance Show ProgramDb instance Read ProgramDb instance Binary ProgramDb -- | This provides an abstraction which deals with configuring and running -- programs. A Program is a static notion of a known program. A -- ConfiguredProgram is a Program that has been found on -- the current machine and is ready to be run (possibly with some -- user-supplied default args). Configuring a program involves finding -- its location and if necessary finding its version. There is also a -- ProgramConfiguration type which holds configured and not-yet -- configured programs. It is the parameter to lots of actions elsewhere -- in Cabal that need to look up and run programs. If we had a Cabal -- monad, the ProgramConfiguration would probably be a reader or -- state component of it. -- -- The module also defines all the known built-in Programs and the -- defaultProgramConfiguration which contains them all. -- -- One nice thing about using it is that any program that is registered -- with Cabal will get some "configure" and ".cabal" helpers like -- --with-foo-args --foo-path= and extra-foo-args. -- -- There's also good default behavior for trying to find "foo" in PATH, -- being able to override its location, etc. -- -- There's also a hook for adding programs in a Setup.lhs script. See -- hookedPrograms in UserHooks. This gives a hook user the ability -- to get the above flags and such so that they don't have to write all -- the PATH logic inside Setup.lhs. module Distribution.Simple.Program -- | Represents a program which can be configured. -- -- Note: rather than constructing this directly, start with -- simpleProgram and override any extra fields. data Program [Program] :: String -> (Verbosity -> ProgramSearchPath -> IO (Maybe FilePath)) -> (Verbosity -> FilePath -> IO (Maybe Version)) -> (Verbosity -> ConfiguredProgram -> IO ConfiguredProgram) -> Program -- | The simple name of the program, eg. ghc [programName] :: Program -> String -- | A function to search for the program if its location was not specified -- by the user. Usually this will just be a call to -- findProgramOnSearchPath. -- -- It is supplied with the prevailing search path which will typically -- just be used as-is, but can be extended or ignored as needed. [programFindLocation] :: Program -> Verbosity -> ProgramSearchPath -> IO (Maybe FilePath) -- | Try to find the version of the program. For many programs this is not -- possible or is not necessary so it's OK to return Nothing. [programFindVersion] :: Program -> Verbosity -> FilePath -> IO (Maybe Version) -- | A function to do any additional configuration after we have located -- the program (and perhaps identified its version). For example it could -- add args, or environment vars. [programPostConf] :: Program -> Verbosity -> ConfiguredProgram -> IO ConfiguredProgram -- | A search path to use when locating executables. This is analogous to -- the unix $PATH or win32 %PATH% but with the ability -- to use the system default method for finding executables -- (findExecutable which on unix is simply looking on the -- $PATH but on win32 is a bit more complicated). -- -- The default to use is [ProgSearchPathDefault] but you can add -- extra dirs either before, after or instead of the default, e.g. here -- we add an extra dir to search after the usual ones. -- --
--   ['ProgramSearchPathDefault', 'ProgramSearchPathDir' dir]
--   
type ProgramSearchPath = [ProgramSearchPathEntry] data ProgramSearchPathEntry -- | A specific dir [ProgramSearchPathDir] :: FilePath -> ProgramSearchPathEntry -- | The system default [ProgramSearchPathDefault] :: ProgramSearchPathEntry -- | Make a simple named program. -- -- By default we'll just search for it in the path and not try to find -- the version name. You can override these behaviours if necessary, eg: -- --
--   simpleProgram "foo" { programFindLocation = ... , programFindVersion ... }
--   
simpleProgram :: String -> Program -- | Look for a program on the path. findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath) -- | Look for a program and try to find it's version number. It can accept -- either an absolute path or the name of a program binary, in which case -- we will look for the program on the path. findProgramVersion :: String -> (String -> String) -> Verbosity -> FilePath -> IO (Maybe Version) -- | Represents a program which has been configured and is thus ready to be -- run. -- -- These are usually made by configuring a Program, but if you -- have to construct one directly then start with -- simpleConfiguredProgram and override any extra fields. data ConfiguredProgram [ConfiguredProgram] :: String -> Maybe Version -> [String] -> [String] -> [(String, Maybe String)] -> Map String String -> ProgramLocation -> ConfiguredProgram -- | Just the name again [programId] :: ConfiguredProgram -> String -- | The version of this program, if it is known. [programVersion] :: ConfiguredProgram -> Maybe Version -- | Default command-line args for this program. These flags will appear -- first on the command line, so they can be overridden by subsequent -- flags. [programDefaultArgs] :: ConfiguredProgram -> [String] -- | Override command-line args for this program. These flags will appear -- last on the command line, so they override all earlier flags. [programOverrideArgs] :: ConfiguredProgram -> [String] -- | Override environment variables for this program. These env vars will -- extend/override the prevailing environment of the current to form the -- environment for the new process. [programOverrideEnv] :: ConfiguredProgram -> [(String, Maybe String)] -- | A key-value map listing various properties of the program, useful for -- feature detection. Populated during the configuration step, key names -- depend on the specific program. [programProperties] :: ConfiguredProgram -> Map String String -- | Location of the program. eg. /usr/bin/ghc-6.4 [programLocation] :: ConfiguredProgram -> ProgramLocation -- | The full path of a configured program. programPath :: ConfiguredProgram -> FilePath type ProgArg = String -- | Where a program was found. Also tells us whether it's specified by -- user or not. This includes not just the path, but the program as well. data ProgramLocation -- | The user gave the path to this program, eg. -- --ghc-path=/usr/bin/ghc-6.6 [UserSpecified] :: FilePath -> ProgramLocation [locationPath] :: ProgramLocation -> FilePath -- | The program was found automatically. [FoundOnSystem] :: FilePath -> ProgramLocation [locationPath] :: ProgramLocation -> FilePath -- | Runs the given configured program. runProgram :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO () -- | Runs the given configured program and gets the output. getProgramOutput :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO String -- | Suppress any extra arguments added by the user. suppressOverrideArgs :: ConfiguredProgram -> ConfiguredProgram -- | Represents a specific invocation of a specific program. -- -- This is used as an intermediate type between deciding how to call a -- program and actually doing it. This provides the opportunity to the -- caller to adjust how the program will be called. These invocations can -- either be run directly or turned into shell or batch scripts. data ProgramInvocation [ProgramInvocation] :: FilePath -> [String] -> [(String, Maybe String)] -> Maybe FilePath -> Maybe String -> IOEncoding -> IOEncoding -> ProgramInvocation [progInvokePath] :: ProgramInvocation -> FilePath [progInvokeArgs] :: ProgramInvocation -> [String] [progInvokeEnv] :: ProgramInvocation -> [(String, Maybe String)] [progInvokeCwd] :: ProgramInvocation -> Maybe FilePath [progInvokeInput] :: ProgramInvocation -> Maybe String [progInvokeInputEncoding] :: ProgramInvocation -> IOEncoding [progInvokeOutputEncoding] :: ProgramInvocation -> IOEncoding emptyProgramInvocation :: ProgramInvocation simpleProgramInvocation :: FilePath -> [String] -> ProgramInvocation programInvocation :: ConfiguredProgram -> [String] -> ProgramInvocation runProgramInvocation :: Verbosity -> ProgramInvocation -> IO () getProgramInvocationOutput :: Verbosity -> ProgramInvocation -> IO String -- | The default list of programs. These programs are typically used -- internally to Cabal. builtinPrograms :: [Program] type ProgramConfiguration = ProgramDb emptyProgramConfiguration :: ProgramConfiguration defaultProgramConfiguration :: ProgramConfiguration restoreProgramConfiguration :: [Program] -> ProgramConfiguration -> ProgramConfiguration -- | Add a known program that we may configure later addKnownProgram :: Program -> ProgramDb -> ProgramDb addKnownPrograms :: [Program] -> ProgramDb -> ProgramDb lookupKnownProgram :: String -> ProgramDb -> Maybe Program knownPrograms :: ProgramDb -> [(Program, Maybe ConfiguredProgram)] -- | Get the current ProgramSearchPath used by the ProgramDb. -- This is the default list of locations where programs are looked for -- when configuring them. This can be overridden for specific programs -- (with userSpecifyPath), and specific known programs can modify -- or ignore this search path in their own configuration code. getProgramSearchPath :: ProgramDb -> ProgramSearchPath -- | Change the current ProgramSearchPath used by the -- ProgramDb. This will affect programs that are configured from -- here on, so you should usually set it before configuring any programs. setProgramSearchPath :: ProgramSearchPath -> ProgramDb -> ProgramDb -- | User-specify this path. Basically override any path information for -- this program in the configuration. If it's not a known program ignore -- it. userSpecifyPath :: String -> FilePath -> ProgramDb -> ProgramDb -- | Like userSpecifyPath but for a list of progs and their paths. userSpecifyPaths :: [(String, FilePath)] -> ProgramDb -> ProgramDb userMaybeSpecifyPath :: String -> Maybe FilePath -> ProgramDb -> ProgramDb -- | User-specify the arguments for this program. Basically override any -- args information for this program in the configuration. If it's not a -- known program, ignore it.. userSpecifyArgs :: String -> [ProgArg] -> ProgramDb -> ProgramDb -- | Like userSpecifyPath but for a list of progs and their args. userSpecifyArgss :: [(String, [ProgArg])] -> ProgramDb -> ProgramDb -- | Get any extra args that have been previously specified for a program. userSpecifiedArgs :: Program -> ProgramDb -> [ProgArg] -- | Try to find a configured program lookupProgram :: Program -> ProgramDb -> Maybe ConfiguredProgram -- | Check that a program is configured and available to be run. -- -- Additionally check that the program version number is suitable and -- return it. For example you could require AnyVersion or -- orLaterVersion (Version [1,0] []) -- -- It returns the configured program, its version number and a possibly -- updated ProgramDb. If the program could not be configured or -- the version is unsuitable, it returns an error value. lookupProgramVersion :: Verbosity -> Program -> VersionRange -> ProgramDb -> IO (Either String (ConfiguredProgram, Version, ProgramDb)) -- | Update a configured program in the database. updateProgram :: ConfiguredProgram -> ProgramDb -> ProgramDb -- | Try to configure a specific program. If the program is already -- included in the collection of unconfigured programs then we use any -- user-supplied location and arguments. If the program gets configured -- successfully it gets added to the configured collection. -- -- Note that it is not a failure if the program cannot be configured. -- It's only a failure if the user supplied a location and the program -- could not be found at that location. -- -- The reason for it not being a failure at this stage is that we don't -- know up front all the programs we will need, so we try to configure -- them all. To verify that a program was actually successfully -- configured use requireProgram. configureProgram :: Verbosity -> Program -> ProgramDb -> IO ProgramDb -- | Try to configure all the known programs that have not yet been -- configured. configureAllKnownPrograms :: Verbosity -> ProgramDb -> IO ProgramDb -- | reconfigure a bunch of programs given new user-specified args. It -- takes the same inputs as userSpecifyPath and -- userSpecifyArgs and for all progs with a new path it calls -- configureProgram. reconfigurePrograms :: Verbosity -> [(String, FilePath)] -> [(String, [ProgArg])] -> ProgramDb -> IO ProgramDb -- | Check that a program is configured and available to be run. -- -- It raises an exception if the program could not be configured, -- otherwise it returns the configured program. requireProgram :: Verbosity -> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb) -- | Like lookupProgramVersion, but raises an exception in case of -- error instead of returning 'Left errMsg'. requireProgramVersion :: Verbosity -> Program -> VersionRange -> ProgramDb -> IO (ConfiguredProgram, Version, ProgramDb) -- | Looks up the given program in the program database and runs it. runDbProgram :: Verbosity -> Program -> ProgramDb -> [ProgArg] -> IO () -- | Looks up the given program in the program database and runs it. getDbProgramOutput :: Verbosity -> Program -> ProgramDb -> [ProgArg] -> IO String ghcProgram :: Program ghcPkgProgram :: Program ghcjsProgram :: Program ghcjsPkgProgram :: Program lhcProgram :: Program lhcPkgProgram :: Program hmakeProgram :: Program jhcProgram :: Program uhcProgram :: Program gccProgram :: Program arProgram :: Program stripProgram :: Program happyProgram :: Program alexProgram :: Program hsc2hsProgram :: Program c2hsProgram :: Program cpphsProgram :: Program hscolourProgram :: Program haddockProgram :: Program greencardProgram :: Program ldProgram :: Program tarProgram :: Program cppProgram :: Program pkgConfigProgram :: Program hpcProgram :: Program rawSystemProgram :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO () rawSystemProgramStdout :: Verbosity -> ConfiguredProgram -> [ProgArg] -> IO String rawSystemProgramConf :: Verbosity -> Program -> ProgramConfiguration -> [ProgArg] -> IO () rawSystemProgramStdoutConf :: Verbosity -> Program -> ProgramConfiguration -> [ProgArg] -> IO String -- | Deprecated: use findProgramLocation instead findProgramOnPath :: String -> Verbosity -> IO (Maybe FilePath) -- | This is a big module, but not very complicated. The code is very -- regular and repetitive. It defines the command line interface for all -- the Cabal commands. For each command (like configure, -- build etc) it defines a type that holds all the flags, the -- default set of flags and a CommandUI that maps command line -- flags to and from the corresponding flags type. -- -- All the flags types are instances of Monoid, see -- http://www.haskell.org/pipermail/cabal-devel/2007-December/001509.html -- for an explanation. -- -- The types defined here get used in the front end and especially in -- cabal-install which has to do quite a bit of manipulating -- sets of command line flags. -- -- This is actually relatively nice, it works quite well. The main change -- it needs is to unify it with the code for managing sets of fields that -- can be read and written from files. This would allow us to save -- configure flags in config files. module Distribution.Simple.Setup -- | Flags that apply at the top level, not to any sub-command. data GlobalFlags [GlobalFlags] :: Flag Bool -> Flag Bool -> GlobalFlags [globalVersion] :: GlobalFlags -> Flag Bool [globalNumericVersion] :: GlobalFlags -> Flag Bool emptyGlobalFlags :: GlobalFlags defaultGlobalFlags :: GlobalFlags globalCommand :: [Command action] -> CommandUI GlobalFlags -- | Flags to configure command. -- -- IMPORTANT: every time a new flag is added, filterConfigureFlags -- should be updated. data ConfigFlags [ConfigFlags] :: ProgramConfiguration -> [(String, FilePath)] -> [(String, [String])] -> NubList FilePath -> Flag CompilerFlavor -> Flag FilePath -> Flag FilePath -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> [String] -> Flag OptimisationLevel -> Flag PathTemplate -> Flag PathTemplate -> InstallDirs (Flag PathTemplate) -> Flag FilePath -> [FilePath] -> [FilePath] -> Flag FilePath -> Flag Verbosity -> Flag Bool -> [Maybe PackageDB] -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> [Dependency] -> [(PackageName, InstalledPackageId)] -> [(ModuleName, (InstalledPackageId, ModuleName))] -> FlagAssignment -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag String -> Flag Bool -> Flag DebugInfoLevel -> ConfigFlags -- | All programs that cabal may run [configPrograms] :: ConfigFlags -> ProgramConfiguration -- | user specified programs paths [configProgramPaths] :: ConfigFlags -> [(String, FilePath)] -- | user specified programs args [configProgramArgs] :: ConfigFlags -> [(String, [String])] -- | Extend the $PATH [configProgramPathExtra] :: ConfigFlags -> NubList FilePath -- | The "flavor" of the compiler, such as GHC or JHC. [configHcFlavor] :: ConfigFlags -> Flag CompilerFlavor -- | given compiler location [configHcPath] :: ConfigFlags -> Flag FilePath -- | given hc-pkg location [configHcPkg] :: ConfigFlags -> Flag FilePath -- | Enable vanilla library [configVanillaLib] :: ConfigFlags -> Flag Bool -- | Enable profiling in the library [configProfLib] :: ConfigFlags -> Flag Bool -- | Build shared library [configSharedLib] :: ConfigFlags -> Flag Bool -- | Enable dynamic linking of the executables. [configDynExe] :: ConfigFlags -> Flag Bool -- | Enable profiling in the executables. [configProfExe] :: ConfigFlags -> Flag Bool -- | Extra arguments to configure [configConfigureArgs] :: ConfigFlags -> [String] -- | Enable optimization. [configOptimization] :: ConfigFlags -> Flag OptimisationLevel -- | Installed executable prefix. [configProgPrefix] :: ConfigFlags -> Flag PathTemplate -- | Installed executable suffix. [configProgSuffix] :: ConfigFlags -> Flag PathTemplate -- | Installation paths [configInstallDirs] :: ConfigFlags -> InstallDirs (Flag PathTemplate) [configScratchDir] :: ConfigFlags -> Flag FilePath -- | path to search for extra libraries [configExtraLibDirs] :: ConfigFlags -> [FilePath] -- | path to search for header files [configExtraIncludeDirs] :: ConfigFlags -> [FilePath] -- | "dist" prefix [configDistPref] :: ConfigFlags -> Flag FilePath -- | verbosity level [configVerbosity] :: ConfigFlags -> Flag Verbosity -- | The --user/--global flag [configUserInstall] :: ConfigFlags -> Flag Bool -- | Which package DBs to use [configPackageDBs] :: ConfigFlags -> [Maybe PackageDB] -- | Enable compiling library for GHCi [configGHCiLib] :: ConfigFlags -> Flag Bool -- | Enable -split-objs with GHC [configSplitObjs] :: ConfigFlags -> Flag Bool -- | Enable executable stripping [configStripExes] :: ConfigFlags -> Flag Bool -- | Enable library stripping [configStripLibs] :: ConfigFlags -> Flag Bool -- | Additional constraints for dependencies. [configConstraints] :: ConfigFlags -> [Dependency] [configDependencies] :: ConfigFlags -> [(PackageName, InstalledPackageId)] -- | The packages depended on. [configInstantiateWith] :: ConfigFlags -> [(ModuleName, (InstalledPackageId, ModuleName))] [configConfigurationsFlags] :: ConfigFlags -> FlagAssignment -- | Enable test suite compilation [configTests] :: ConfigFlags -> Flag Bool -- | Enable benchmark compilation [configBenchmarks] :: ConfigFlags -> Flag Bool -- | Enable program coverage [configCoverage] :: ConfigFlags -> Flag Bool -- | Enable program coverage (deprecated) [configLibCoverage] :: ConfigFlags -> Flag Bool -- | All direct dependencies and flags are provided on the command line by -- the user via the '--dependency' and '--flags' options. [configExactConfiguration] :: ConfigFlags -> Flag Bool -- | Halt and show an error message indicating an error in flag assignment [configFlagError] :: ConfigFlags -> Flag String -- | Enable relocatable package built [configRelocatable] :: ConfigFlags -> Flag Bool -- | Emit debug info. [configDebugInfo] :: ConfigFlags -> Flag DebugInfoLevel emptyConfigFlags :: ConfigFlags defaultConfigFlags :: ProgramConfiguration -> ConfigFlags configureCommand :: ProgramConfiguration -> CommandUI ConfigFlags configAbsolutePaths :: ConfigFlags -> IO ConfigFlags readPackageDbList :: String -> [Maybe PackageDB] showPackageDbList :: [Maybe PackageDB] -> [String] -- | Flags to copy: (destdir, copy-prefix (backwards compat), -- verbosity) data CopyFlags [CopyFlags] :: Flag CopyDest -> Flag FilePath -> Flag Verbosity -> CopyFlags [copyDest] :: CopyFlags -> Flag CopyDest [copyDistPref] :: CopyFlags -> Flag FilePath [copyVerbosity] :: CopyFlags -> Flag Verbosity emptyCopyFlags :: CopyFlags defaultCopyFlags :: CopyFlags copyCommand :: CommandUI CopyFlags -- | Flags to install: (package db, verbosity) data InstallFlags [InstallFlags] :: Flag PackageDB -> Flag FilePath -> Flag Bool -> Flag Bool -> Flag Verbosity -> InstallFlags [installPackageDB] :: InstallFlags -> Flag PackageDB [installDistPref] :: InstallFlags -> Flag FilePath [installUseWrapper] :: InstallFlags -> Flag Bool [installInPlace] :: InstallFlags -> Flag Bool [installVerbosity] :: InstallFlags -> Flag Verbosity emptyInstallFlags :: InstallFlags defaultInstallFlags :: InstallFlags installCommand :: CommandUI InstallFlags data HaddockFlags [HaddockFlags] :: [(String, FilePath)] -> [(String, [String])] -> Flag Bool -> Flag Bool -> Flag String -> Flag Bool -> Flag Bool -> Flag Bool -> Flag Bool -> Flag FilePath -> Flag Bool -> Flag FilePath -> Flag PathTemplate -> Flag FilePath -> Flag Bool -> Flag Verbosity -> HaddockFlags [haddockProgramPaths] :: HaddockFlags -> [(String, FilePath)] [haddockProgramArgs] :: HaddockFlags -> [(String, [String])] [haddockHoogle] :: HaddockFlags -> Flag Bool [haddockHtml] :: HaddockFlags -> Flag Bool [haddockHtmlLocation] :: HaddockFlags -> Flag String [haddockExecutables] :: HaddockFlags -> Flag Bool [haddockTestSuites] :: HaddockFlags -> Flag Bool [haddockBenchmarks] :: HaddockFlags -> Flag Bool [haddockInternal] :: HaddockFlags -> Flag Bool [haddockCss] :: HaddockFlags -> Flag FilePath [haddockHscolour] :: HaddockFlags -> Flag Bool [haddockHscolourCss] :: HaddockFlags -> Flag FilePath [haddockContents] :: HaddockFlags -> Flag PathTemplate [haddockDistPref] :: HaddockFlags -> Flag FilePath [haddockKeepTempFiles] :: HaddockFlags -> Flag Bool [haddockVerbosity] :: HaddockFlags -> Flag Verbosity emptyHaddockFlags :: HaddockFlags defaultHaddockFlags :: HaddockFlags haddockCommand :: CommandUI HaddockFlags data HscolourFlags [HscolourFlags] :: Flag FilePath -> Flag Bool -> Flag Bool -> Flag Bool -> Flag FilePath -> Flag Verbosity -> HscolourFlags [hscolourCSS] :: HscolourFlags -> Flag FilePath [hscolourExecutables] :: HscolourFlags -> Flag Bool [hscolourTestSuites] :: HscolourFlags -> Flag Bool [hscolourBenchmarks] :: HscolourFlags -> Flag Bool [hscolourDistPref] :: HscolourFlags -> Flag FilePath [hscolourVerbosity] :: HscolourFlags -> Flag Verbosity emptyHscolourFlags :: HscolourFlags defaultHscolourFlags :: HscolourFlags hscolourCommand :: CommandUI HscolourFlags data BuildFlags [BuildFlags] :: [(String, FilePath)] -> [(String, [String])] -> Flag FilePath -> Flag Verbosity -> Flag (Maybe Int) -> [String] -> BuildFlags [buildProgramPaths] :: BuildFlags -> [(String, FilePath)] [buildProgramArgs] :: BuildFlags -> [(String, [String])] [buildDistPref] :: BuildFlags -> Flag FilePath [buildVerbosity] :: BuildFlags -> Flag Verbosity [buildNumJobs] :: BuildFlags -> Flag (Maybe Int) [buildArgs] :: BuildFlags -> [String] emptyBuildFlags :: BuildFlags defaultBuildFlags :: BuildFlags buildCommand :: ProgramConfiguration -> CommandUI BuildFlags -- | Deprecated: Use buildVerbosity instead buildVerbose :: BuildFlags -> Verbosity data ReplFlags [ReplFlags] :: [(String, FilePath)] -> [(String, [String])] -> Flag FilePath -> Flag Verbosity -> Flag Bool -> ReplFlags [replProgramPaths] :: ReplFlags -> [(String, FilePath)] [replProgramArgs] :: ReplFlags -> [(String, [String])] [replDistPref] :: ReplFlags -> Flag FilePath [replVerbosity] :: ReplFlags -> Flag Verbosity [replReload] :: ReplFlags -> Flag Bool defaultReplFlags :: ReplFlags replCommand :: ProgramConfiguration -> CommandUI ReplFlags data CleanFlags [CleanFlags] :: Flag Bool -> Flag FilePath -> Flag Verbosity -> CleanFlags [cleanSaveConf] :: CleanFlags -> Flag Bool [cleanDistPref] :: CleanFlags -> Flag FilePath [cleanVerbosity] :: CleanFlags -> Flag Verbosity emptyCleanFlags :: CleanFlags defaultCleanFlags :: CleanFlags cleanCommand :: CommandUI CleanFlags -- | Flags to register and unregister: (user package, -- gen-script, in-place, verbosity) data RegisterFlags [RegisterFlags] :: Flag PackageDB -> Flag Bool -> Flag (Maybe FilePath) -> Flag Bool -> Flag FilePath -> Flag Bool -> Flag Verbosity -> RegisterFlags [regPackageDB] :: RegisterFlags -> Flag PackageDB [regGenScript] :: RegisterFlags -> Flag Bool [regGenPkgConf] :: RegisterFlags -> Flag (Maybe FilePath) [regInPlace] :: RegisterFlags -> Flag Bool [regDistPref] :: RegisterFlags -> Flag FilePath [regPrintId] :: RegisterFlags -> Flag Bool [regVerbosity] :: RegisterFlags -> Flag Verbosity emptyRegisterFlags :: RegisterFlags defaultRegisterFlags :: RegisterFlags registerCommand :: CommandUI RegisterFlags unregisterCommand :: CommandUI RegisterFlags -- | Flags to sdist: (snapshot, verbosity) data SDistFlags [SDistFlags] :: Flag Bool -> Flag FilePath -> Flag FilePath -> Flag FilePath -> Flag Verbosity -> SDistFlags [sDistSnapshot] :: SDistFlags -> Flag Bool [sDistDirectory] :: SDistFlags -> Flag FilePath [sDistDistPref] :: SDistFlags -> Flag FilePath [sDistListSources] :: SDistFlags -> Flag FilePath [sDistVerbosity] :: SDistFlags -> Flag Verbosity emptySDistFlags :: SDistFlags defaultSDistFlags :: SDistFlags sdistCommand :: CommandUI SDistFlags data TestFlags [TestFlags] :: Flag FilePath -> Flag Verbosity -> Flag PathTemplate -> Flag PathTemplate -> Flag TestShowDetails -> Flag Bool -> [PathTemplate] -> TestFlags [testDistPref] :: TestFlags -> Flag FilePath [testVerbosity] :: TestFlags -> Flag Verbosity [testHumanLog] :: TestFlags -> Flag PathTemplate [testMachineLog] :: TestFlags -> Flag PathTemplate [testShowDetails] :: TestFlags -> Flag TestShowDetails [testKeepTix] :: TestFlags -> Flag Bool [testOptions] :: TestFlags -> [PathTemplate] emptyTestFlags :: TestFlags defaultTestFlags :: TestFlags testCommand :: CommandUI TestFlags data TestShowDetails [Never] :: TestShowDetails [Failures] :: TestShowDetails [Always] :: TestShowDetails [Streaming] :: TestShowDetails data BenchmarkFlags [BenchmarkFlags] :: Flag FilePath -> Flag Verbosity -> [PathTemplate] -> BenchmarkFlags [benchmarkDistPref] :: BenchmarkFlags -> Flag FilePath [benchmarkVerbosity] :: BenchmarkFlags -> Flag Verbosity [benchmarkOptions] :: BenchmarkFlags -> [PathTemplate] emptyBenchmarkFlags :: BenchmarkFlags defaultBenchmarkFlags :: BenchmarkFlags benchmarkCommand :: CommandUI BenchmarkFlags -- | The location prefix for the copy command. data CopyDest [NoCopyDest] :: CopyDest [CopyTo] :: FilePath -> CopyDest -- | Arguments to pass to a configure script, e.g. generated by -- autoconf. configureArgs :: Bool -> ConfigFlags -> [String] configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags] configureCCompiler :: Verbosity -> ProgramConfiguration -> IO (FilePath, [String]) configureLinker :: Verbosity -> ProgramConfiguration -> IO (FilePath, [String]) buildOptions :: ProgramConfiguration -> ShowOrParseArgs -> [OptionField BuildFlags] haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags] installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))] -- | For each known program PROG in progConf, produce a -- PROG-options OptionField. programConfigurationOptions :: ProgramConfiguration -> ShowOrParseArgs -> (flags -> [(String, [String])]) -> ([(String, [String])] -> (flags -> flags)) -> [OptionField flags] -- | Like programConfigurationPaths, but allows to customise the -- option name. programConfigurationPaths' :: (String -> String) -> ProgramConfiguration -> ShowOrParseArgs -> (flags -> [(String, FilePath)]) -> ([(String, FilePath)] -> (flags -> flags)) -> [OptionField flags] defaultDistPref :: FilePath -- | All flags are monoids, they come in two flavours: -- --
    --
  1. list flags eg
  2. --
-- --
--   --ghc-option=foo --ghc-option=bar
--   
-- -- gives us all the values ["foo", "bar"] -- --
    --
  1. singular value flags, eg:
  2. --
-- --
--   --enable-foo --disable-foo
--   
-- -- gives us Just False So this Flag type is for the latter singular kind -- of flag. Its monoid instance gives us the behaviour where it starts -- out as NoFlag and later flags override earlier ones. data Flag a [Flag] :: a -> Flag a [NoFlag] :: Flag a toFlag :: a -> Flag a fromFlag :: Flag a -> a fromFlagOrDefault :: a -> Flag a -> a flagToMaybe :: Flag a -> Maybe a flagToList :: Flag a -> [a] boolOpt :: SFlags -> SFlags -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a boolOpt' :: OptFlags -> OptFlags -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a trueArg :: MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a falseArg :: MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a optionVerbosity :: (flags -> Flag Verbosity) -> (Flag Verbosity -> flags -> flags) -> OptionField flags optionNumJobs :: (flags -> Flag (Maybe Int)) -> (Flag (Maybe Int) -> flags -> flags) -> OptionField flags instance Selector S1_0_39ConfigFlags instance Selector S1_0_38ConfigFlags instance Selector S1_0_37ConfigFlags instance Selector S1_0_36ConfigFlags instance Selector S1_0_35ConfigFlags instance Selector S1_0_34ConfigFlags instance Selector S1_0_33ConfigFlags instance Selector S1_0_32ConfigFlags instance Selector S1_0_31ConfigFlags instance Selector S1_0_30ConfigFlags instance Selector S1_0_29ConfigFlags instance Selector S1_0_28ConfigFlags instance Selector S1_0_27ConfigFlags instance Selector S1_0_26ConfigFlags instance Selector S1_0_25ConfigFlags instance Selector S1_0_24ConfigFlags instance Selector S1_0_23ConfigFlags instance Selector S1_0_22ConfigFlags instance Selector S1_0_21ConfigFlags instance Selector S1_0_20ConfigFlags instance Selector S1_0_19ConfigFlags instance Selector S1_0_18ConfigFlags instance Selector S1_0_17ConfigFlags instance Selector S1_0_16ConfigFlags instance Selector S1_0_15ConfigFlags instance Selector S1_0_14ConfigFlags instance Selector S1_0_13ConfigFlags instance Selector S1_0_12ConfigFlags instance Selector S1_0_11ConfigFlags instance Selector S1_0_10ConfigFlags instance Selector S1_0_9ConfigFlags instance Selector S1_0_8ConfigFlags instance Selector S1_0_7ConfigFlags instance Selector S1_0_6ConfigFlags instance Selector S1_0_5ConfigFlags instance Selector S1_0_4ConfigFlags instance Selector S1_0_3ConfigFlags instance Selector S1_0_2ConfigFlags instance Selector S1_0_1ConfigFlags instance Selector S1_0_0ConfigFlags instance Constructor C1_0ConfigFlags instance Datatype D1ConfigFlags instance Constructor C1_1Flag instance Constructor C1_0Flag instance Datatype D1Flag instance Show TestShowDetails instance Bounded TestShowDetails instance Enum TestShowDetails instance Ord TestShowDetails instance Eq TestShowDetails instance Show ReplFlags instance Show BuildFlags instance Show CleanFlags instance Show HaddockFlags instance Show HscolourFlags instance Show RegisterFlags instance Show SDistFlags instance Show InstallFlags instance Show CopyFlags instance Show ConfigFlags instance Read ConfigFlags instance Generic ConfigFlags instance Read a => Read (Flag a) instance Show a => Show (Flag a) instance Generic (Flag a) instance Eq a => Eq (Flag a) instance Binary a => Binary (Flag a) instance Functor Flag instance Monoid (Flag a) instance Bounded a => Bounded (Flag a) instance Enum a => Enum (Flag a) instance Monoid GlobalFlags instance Binary ConfigFlags instance Monoid ConfigFlags instance Monoid CopyFlags instance Monoid InstallFlags instance Monoid SDistFlags instance Monoid RegisterFlags instance Monoid HscolourFlags instance Monoid HaddockFlags instance Monoid CleanFlags instance Monoid BuildFlags instance Monoid ReplFlags instance Text TestShowDetails instance Monoid TestShowDetails instance Monoid TestFlags instance Monoid BenchmarkFlags -- | This is an alternative build system that delegates everything to the -- make program. All the commands just end up calling -- make with appropriate arguments. The intention was to allow -- preexisting packages that used makefiles to be wrapped into Cabal -- packages. In practice essentially all such packages were converted -- over to the "Simple" build system instead. Consequently this module is -- not used much and it certainly only sees cursory maintenance and no -- testing. Perhaps at some point we should stop pretending that it -- works. -- -- Uses the parsed command-line from Distribution.Simple.Setup in -- order to build Haskell tools using a back-end build system based on -- make. Obviously we assume that there is a configure script, and that -- after the ConfigCmd has been run, there is a Makefile. Further -- assumptions: -- -- module Distribution.Make -- | Indicates the license under which a package's source code is released. -- Versions of the licenses not listed here will be rejected by Hackage -- and cause cabal check to issue a warning. data License -- | GNU General Public License, version 2 or version 3. [GPL] :: (Maybe Version) -> License -- | GNU Affero General Public License, version 3. [AGPL] :: (Maybe Version) -> License -- | GNU Lesser General Public License, version 2.1 or version -- 3. [LGPL] :: (Maybe Version) -> License -- | 2-clause BSD license. [BSD2] :: License -- | 3-clause BSD license. [BSD3] :: License -- | 4-clause BSD license. This license has not been approved by the -- OSI and is incompatible with the GNU GPL. It is provided for -- historical reasons and should be avoided. [BSD4] :: License -- | MIT license. [MIT] :: License -- | ISC license [ISC] :: License -- | Mozilla Public License, version 2.0. [MPL] :: Version -> License -- | Apache License, version 2.0. [Apache] :: (Maybe Version) -> License -- | The author of a package disclaims any copyright to its source code and -- dedicates it to the public domain. This is not a software license. -- Please note that it is not possible to dedicate works to the public -- domain in every jurisdiction, nor is a work that is in the public -- domain in one jurisdiction necessarily in the public domain elsewhere. [PublicDomain] :: License -- | Explicitly 'All Rights Reserved', eg for proprietary software. The -- package may not be legally modified or redistributed by anyone but the -- rightsholder. [AllRightsReserved] :: License -- | No license specified which legally defaults to 'All Rights Reserved'. -- The package may not be legally modified or redistributed by anyone but -- the rightsholder. [UnspecifiedLicense] :: License -- | Any other software license. [OtherLicense] :: License -- | Indicates an erroneous license name. [UnknownLicense] :: String -> License -- | A Version represents the version of a software entity. -- -- An instance of Eq is provided, which implements exact equality -- modulo reordering of the tags in the versionTags field. -- -- An instance of Ord is also provided, which gives lexicographic -- ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 -- > 1.2.2, etc.). This is expected to be sufficient for many uses, -- but note that you may need to use a more specific ordering for your -- versioning scheme. For example, some versioning schemes may include -- pre-releases which have tags "pre1", "pre2", and so -- on, and these would need to be taken into account when determining -- ordering. In some cases, date ordering may be more appropriate, so the -- application would have to look for date tags in the -- versionTags field and compare those. The bottom line is, don't -- always assume that compare and other Ord operations are -- the right thing for every Version. -- -- Similarly, concrete representations of versions may differ. One -- possible concrete representation is provided (see showVersion -- and parseVersion), but depending on the application a different -- concrete representation may be more appropriate. data Version :: * [Version] :: [Int] -> [String] -> Version -- | The numeric branch for this version. This reflects the fact that most -- software versions are tree-structured; there is a main trunk which is -- tagged with versions at various points (1,2,3...), and the first -- branch off the trunk after version 3 is 3.1, the second branch off the -- trunk after version 3 is 3.2, and so on. The tree can be branched -- arbitrarily, just by adding more digits. -- -- We represent the branch as a list of Int, so version 3.2.1 -- becomes [3,2,1]. Lexicographic ordering (i.e. the default instance of -- Ord for [Int]) gives the natural ordering of branches. [versionBranch] :: Version -> [Int] -- | A version can be tagged with an arbitrary list of strings. The -- interpretation of the list of tags is entirely dependent on the entity -- that this version applies to. [versionTags] :: Version -> [String] defaultMain :: IO () defaultMainArgs :: [String] -> IO () -- | Deprecated: it ignores its PackageDescription arg defaultMainNoRead :: PackageDescription -> IO () module Distribution.Simple.Program.GHC -- | A structured set of GHC options/flags data GhcOptions [GhcOptions] :: Flag GhcMode -> NubListR String -> NubListR String -> NubListR FilePath -> NubListR ModuleName -> Flag FilePath -> Flag FilePath -> Flag Bool -> NubListR FilePath -> Flag PackageKey -> PackageDBStack -> NubListR (InstalledPackageId, PackageId, ModuleRenaming) -> Flag Bool -> Flag Bool -> [(ModuleName, (PackageKey, ModuleName))] -> NubListR FilePath -> NubListR FilePath -> NubListR String -> NubListR String -> Flag Bool -> Flag Bool -> NubListR String -> NubListR String -> NubListR FilePath -> NubListR FilePath -> NubListR FilePath -> Flag Language -> NubListR Extension -> Map Extension String -> Flag GhcOptimisation -> Flag Bool -> Flag Bool -> Flag Bool -> Flag (Maybe Int) -> Flag FilePath -> NubListR FilePath -> Flag String -> Flag String -> Flag String -> Flag String -> Flag FilePath -> Flag FilePath -> Flag FilePath -> Flag FilePath -> Flag GhcDynLinkMode -> Flag Bool -> Flag Bool -> Flag String -> NubListR FilePath -> Flag Verbosity -> Flag Bool -> GhcOptions -- | The major mode for the ghc invocation. [ghcOptMode] :: GhcOptions -> Flag GhcMode -- | Any extra options to pass directly to ghc. These go at the end and -- hence override other stuff. [ghcOptExtra] :: GhcOptions -> NubListR String -- | Extra default flags to pass directly to ghc. These go at the beginning -- and so can be overridden by other stuff. [ghcOptExtraDefault] :: GhcOptions -> NubListR String -- | The main input files; could be .hs, .hi, .c, .o, depending on mode. [ghcOptInputFiles] :: GhcOptions -> NubListR FilePath -- | The names of input Haskell modules, mainly for --make mode. [ghcOptInputModules] :: GhcOptions -> NubListR ModuleName -- | Location for output file; the ghc -o flag. [ghcOptOutputFile] :: GhcOptions -> Flag FilePath -- | Location for dynamic output file in GhcStaticAndDynamic mode; -- the ghc -dyno flag. [ghcOptOutputDynFile] :: GhcOptions -> Flag FilePath -- | Start with an empty search path for Haskell source files; the ghc -- -i flag (-i on it's own with no path argument). [ghcOptSourcePathClear] :: GhcOptions -> Flag Bool -- | Search path for Haskell source files; the ghc -i flag. [ghcOptSourcePath] :: GhcOptions -> NubListR FilePath -- | The package key the modules will belong to; the ghc -- -this-package-key flag. [ghcOptPackageKey] :: GhcOptions -> Flag PackageKey -- | GHC package databases to use, the ghc -package-conf flag. [ghcOptPackageDBs] :: GhcOptions -> PackageDBStack -- | The GHC packages to use. For compatability with old and new ghc, this -- requires both the short and long form of the package id; the ghc -- -package or ghc -package-id flags. [ghcOptPackages] :: GhcOptions -> NubListR (InstalledPackageId, PackageId, ModuleRenaming) -- | Start with a clean package set; the ghc -hide-all-packages -- flag [ghcOptHideAllPackages] :: GhcOptions -> Flag Bool -- | Don't automatically link in Haskell98 etc; the ghc -- -no-auto-link-packages flag. [ghcOptNoAutoLinkPackages] :: GhcOptions -> Flag Bool -- | What packages are implementing the signatures [ghcOptSigOf] :: GhcOptions -> [(ModuleName, (PackageKey, ModuleName))] -- | Names of libraries to link in; the ghc -l flag. [ghcOptLinkLibs] :: GhcOptions -> NubListR FilePath -- | Search path for libraries to link in; the ghc -L flag. [ghcOptLinkLibPath] :: GhcOptions -> NubListR FilePath -- | Options to pass through to the linker; the ghc -optl flag. [ghcOptLinkOptions] :: GhcOptions -> NubListR String -- | OSX only: frameworks to link in; the ghc -framework flag. [ghcOptLinkFrameworks] :: GhcOptions -> NubListR String -- | Don't do the link step, useful in make mode; the ghc -no-link -- flag. [ghcOptNoLink] :: GhcOptions -> Flag Bool -- | Don't link in the normal RTS main entry point; the ghc -- -no-hs-main flag. [ghcOptLinkNoHsMain] :: GhcOptions -> Flag Bool -- | Options to pass through to the C compiler; the ghc -optc -- flag. [ghcOptCcOptions] :: GhcOptions -> NubListR String -- | Options to pass through to CPP; the ghc -optP flag. [ghcOptCppOptions] :: GhcOptions -> NubListR String -- | Search path for CPP includes like header files; the ghc -I -- flag. [ghcOptCppIncludePath] :: GhcOptions -> NubListR FilePath -- | Extra header files to include at CPP stage; the ghc -- -optP-include flag. [ghcOptCppIncludes] :: GhcOptions -> NubListR FilePath -- | Extra header files to include for old-style FFI; the ghc -- -#include flag. [ghcOptFfiIncludes] :: GhcOptions -> NubListR FilePath -- | The base language; the ghc -XHaskell98 or -- -XHaskell2010 flag. [ghcOptLanguage] :: GhcOptions -> Flag Language -- | The language extensions; the ghc -X flag. [ghcOptExtensions] :: GhcOptions -> NubListR Extension -- | A GHC version-dependent mapping of extensions to flags. This must be -- set to be able to make use of the ghcOptExtensions. [ghcOptExtensionMap] :: GhcOptions -> Map Extension String -- | What optimisation level to use; the ghc -O flag. [ghcOptOptimisation] :: GhcOptions -> Flag GhcOptimisation -- | Emit debug info; the ghc -g flag. [ghcOptDebugInfo] :: GhcOptions -> Flag Bool -- | Compile in profiling mode; the ghc -prof flag. [ghcOptProfilingMode] :: GhcOptions -> Flag Bool -- | Use the "split object files" feature; the ghc -split-objs -- flag. [ghcOptSplitObjs] :: GhcOptions -> Flag Bool -- | Run N jobs simultaneously (if possible). [ghcOptNumJobs] :: GhcOptions -> Flag (Maybe Int) -- | Enable coverage analysis; the ghc -fhpc -hpcdir flags. [ghcOptHPCDir] :: GhcOptions -> Flag FilePath -- | Extra GHCi startup scripts; the -ghci-script flag [ghcOptGHCiScripts] :: GhcOptions -> NubListR FilePath [ghcOptHiSuffix] :: GhcOptions -> Flag String [ghcOptObjSuffix] :: GhcOptions -> Flag String -- | only in GhcStaticAndDynamic mode [ghcOptDynHiSuffix] :: GhcOptions -> Flag String -- | only in GhcStaticAndDynamic mode [ghcOptDynObjSuffix] :: GhcOptions -> Flag String [ghcOptHiDir] :: GhcOptions -> Flag FilePath [ghcOptObjDir] :: GhcOptions -> Flag FilePath [ghcOptOutputDir] :: GhcOptions -> Flag FilePath [ghcOptStubDir] :: GhcOptions -> Flag FilePath [ghcOptDynLinkMode] :: GhcOptions -> Flag GhcDynLinkMode [ghcOptShared] :: GhcOptions -> Flag Bool [ghcOptFPic] :: GhcOptions -> Flag Bool [ghcOptDylibName] :: GhcOptions -> Flag String [ghcOptRPaths] :: GhcOptions -> NubListR FilePath -- | Get GHC to be quiet or verbose with what it's doing; the ghc -- -v flag. [ghcOptVerbosity] :: GhcOptions -> Flag Verbosity -- | Let GHC know that it is Cabal that's calling it. Modifies some of the -- GHC error messages. [ghcOptCabal] :: GhcOptions -> Flag Bool data GhcMode -- |
--   ghc -c
--   
[GhcModeCompile] :: GhcMode -- |
--   ghc
--   
[GhcModeLink] :: GhcMode -- |
--   ghc --make
--   
[GhcModeMake] :: GhcMode -- | ghci / ghc --interactive [GhcModeInteractive] :: GhcMode -- | ghc --abi-hash | GhcModeDepAnalysis -- ^ ghc -M | -- GhcModeEvaluate -- ^ ghc -e [GhcModeAbiHash] :: GhcMode data GhcOptimisation -- |
--   -O0
--   
[GhcNoOptimisation] :: GhcOptimisation -- |
--   -O
--   
[GhcNormalOptimisation] :: GhcOptimisation -- |
--   -O2
--   
[GhcMaximumOptimisation] :: GhcOptimisation -- | e.g. -Odph [GhcSpecialOptimisation] :: String -> GhcOptimisation data GhcDynLinkMode -- |
--   -static
--   
[GhcStaticOnly] :: GhcDynLinkMode -- |
--   -dynamic
--   
[GhcDynamicOnly] :: GhcDynLinkMode -- |
--   -static -dynamic-too
--   
[GhcStaticAndDynamic] :: GhcDynLinkMode ghcInvocation :: ConfiguredProgram -> Compiler -> GhcOptions -> ProgramInvocation renderGhcOptions :: Compiler -> GhcOptions -> [String] runGHC :: Verbosity -> ConfiguredProgram -> Compiler -> GhcOptions -> IO () instance Show GhcOptions instance Eq GhcDynLinkMode instance Show GhcDynLinkMode instance Eq GhcOptimisation instance Show GhcOptimisation instance Eq GhcMode instance Show GhcMode instance Monoid GhcOptions -- | Once a package has been configured we have resolved conditionals and -- dependencies, configured the compiler and other needed external -- programs. The LocalBuildInfo is used to hold all this -- information. It holds the install dirs, the compiler, the exact -- package dependencies, the configured programs, the package database to -- use and a bunch of miscellaneous configure flags. It gets saved and -- reloaded from a file (dist/setup-config). It gets passed in -- to very many subsequent build actions. module Distribution.Simple.LocalBuildInfo -- | Data cached after configuration step. See also ConfigFlags. data LocalBuildInfo [LocalBuildInfo] :: ConfigFlags -> [String] -> InstallDirTemplates -> Compiler -> Platform -> FilePath -> [(ComponentName, ComponentLocalBuildInfo, [ComponentName])] -> InstalledPackageIndex -> Maybe FilePath -> PackageDescription -> PackageKey -> [(ModuleName, (InstalledPackageInfo, ModuleName))] -> ProgramConfiguration -> PackageDBStack -> Bool -> Bool -> Bool -> Bool -> Bool -> OptimisationLevel -> DebugInfoLevel -> Bool -> Bool -> Bool -> Bool -> PathTemplate -> PathTemplate -> Bool -> LocalBuildInfo -- | Options passed to the configuration step. Needed to re-run -- configuration when .cabal is out of date [configFlags] :: LocalBuildInfo -> ConfigFlags -- | Extra args on the command line for the configuration step. Needed to -- re-run configuration when .cabal is out of date [extraConfigArgs] :: LocalBuildInfo -> [String] -- | The installation directories for the various different kinds of files -- TODO: inplaceDirTemplates :: InstallDirs FilePath [installDirTemplates] :: LocalBuildInfo -> InstallDirTemplates -- | The compiler we're building with [compiler] :: LocalBuildInfo -> Compiler -- | The platform we're building for [hostPlatform] :: LocalBuildInfo -> Platform -- | Where to build the package. [buildDir] :: LocalBuildInfo -> FilePath -- | All the components to build, ordered by topological sort, and with -- their dependencies over the intrapackage dependency graph [componentsConfigs] :: LocalBuildInfo -> [(ComponentName, ComponentLocalBuildInfo, [ComponentName])] -- | All the info about the installed packages that the current package -- depends on (directly or indirectly). [installedPkgs] :: LocalBuildInfo -> InstalledPackageIndex -- | the filename containing the .cabal file, if available [pkgDescrFile] :: LocalBuildInfo -> Maybe FilePath -- | The resolved package description, that does not contain any -- conditionals. [localPkgDescr] :: LocalBuildInfo -> PackageDescription -- | The package key for the current build, calculated from the package ID -- and the dependency graph. [pkgKey] :: LocalBuildInfo -> PackageKey [instantiatedWith] :: LocalBuildInfo -> [(ModuleName, (InstalledPackageInfo, ModuleName))] -- | Location and args for all programs [withPrograms] :: LocalBuildInfo -> ProgramConfiguration -- | What package database to use, global/user [withPackageDB] :: LocalBuildInfo -> PackageDBStack -- | Whether to build normal libs. [withVanillaLib] :: LocalBuildInfo -> Bool -- | Whether to build profiling versions of libs. [withProfLib] :: LocalBuildInfo -> Bool -- | Whether to build shared versions of libs. [withSharedLib] :: LocalBuildInfo -> Bool -- | Whether to link executables dynamically [withDynExe] :: LocalBuildInfo -> Bool -- | Whether to build executables for profiling. [withProfExe] :: LocalBuildInfo -> Bool -- | Whether to build with optimization (if available). [withOptimization] :: LocalBuildInfo -> OptimisationLevel -- | Whether to emit debug info (if available). [withDebugInfo] :: LocalBuildInfo -> DebugInfoLevel -- | Whether to build libs suitable for use with GHCi. [withGHCiLib] :: LocalBuildInfo -> Bool -- | Use -split-objs with GHC, if available [splitObjs] :: LocalBuildInfo -> Bool -- | Whether to strip executables during install [stripExes] :: LocalBuildInfo -> Bool -- | Whether to strip libraries during install [stripLibs] :: LocalBuildInfo -> Bool -- | Prefix to be prepended to installed executables [progPrefix] :: LocalBuildInfo -> PathTemplate -- | Suffix to be appended to installed executables [progSuffix] :: LocalBuildInfo -> PathTemplate [relocatable] :: LocalBuildInfo -> Bool -- | External package dependencies for the package as a whole. This is the -- union of the individual componentPackageDeps, less any internal -- deps. externalPackageDeps :: LocalBuildInfo -> [(InstalledPackageId, PackageId)] -- | The installed package Id we use for local packages registered in the -- local package db. This is what is used for intra-package deps between -- components. inplacePackageId :: PackageId -> InstalledPackageId data Component [CLib] :: Library -> Component [CExe] :: Executable -> Component [CTest] :: TestSuite -> Component [CBench] :: Benchmark -> Component data ComponentName [CLibName] :: ComponentName [CExeName] :: String -> ComponentName [CTestName] :: String -> ComponentName [CBenchName] :: String -> ComponentName showComponentName :: ComponentName -> String data ComponentLocalBuildInfo [LibComponentLocalBuildInfo] :: [(InstalledPackageId, PackageId)] -> [ExposedModule] -> Map PackageName ModuleRenaming -> [LibraryName] -> ComponentLocalBuildInfo -- | Resolved internal and external package dependencies for this -- component. The BuildInfo specifies a set of build dependencies -- that must be satisfied in terms of version ranges. This field fixes -- those dependencies to the specific versions available on this machine -- for this compiler. [componentPackageDeps] :: ComponentLocalBuildInfo -> [(InstalledPackageId, PackageId)] [componentExposedModules] :: ComponentLocalBuildInfo -> [ExposedModule] [componentPackageRenaming] :: ComponentLocalBuildInfo -> Map PackageName ModuleRenaming [componentLibraries] :: ComponentLocalBuildInfo -> [LibraryName] [ExeComponentLocalBuildInfo] :: [(InstalledPackageId, PackageId)] -> Map PackageName ModuleRenaming -> ComponentLocalBuildInfo -- | Resolved internal and external package dependencies for this -- component. The BuildInfo specifies a set of build dependencies -- that must be satisfied in terms of version ranges. This field fixes -- those dependencies to the specific versions available on this machine -- for this compiler. [componentPackageDeps] :: ComponentLocalBuildInfo -> [(InstalledPackageId, PackageId)] [componentPackageRenaming] :: ComponentLocalBuildInfo -> Map PackageName ModuleRenaming [TestComponentLocalBuildInfo] :: [(InstalledPackageId, PackageId)] -> Map PackageName ModuleRenaming -> ComponentLocalBuildInfo -- | Resolved internal and external package dependencies for this -- component. The BuildInfo specifies a set of build dependencies -- that must be satisfied in terms of version ranges. This field fixes -- those dependencies to the specific versions available on this machine -- for this compiler. [componentPackageDeps] :: ComponentLocalBuildInfo -> [(InstalledPackageId, PackageId)] [componentPackageRenaming] :: ComponentLocalBuildInfo -> Map PackageName ModuleRenaming [BenchComponentLocalBuildInfo] :: [(InstalledPackageId, PackageId)] -> Map PackageName ModuleRenaming -> ComponentLocalBuildInfo -- | Resolved internal and external package dependencies for this -- component. The BuildInfo specifies a set of build dependencies -- that must be satisfied in terms of version ranges. This field fixes -- those dependencies to the specific versions available on this machine -- for this compiler. [componentPackageDeps] :: ComponentLocalBuildInfo -> [(InstalledPackageId, PackageId)] [componentPackageRenaming] :: ComponentLocalBuildInfo -> Map PackageName ModuleRenaming data LibraryName [LibraryName] :: String -> LibraryName foldComponent :: (Library -> a) -> (Executable -> a) -> (TestSuite -> a) -> (Benchmark -> a) -> Component -> a componentName :: Component -> ComponentName componentBuildInfo :: Component -> BuildInfo componentEnabled :: Component -> Bool componentDisabledReason :: Component -> Maybe ComponentDisabledReason data ComponentDisabledReason [DisabledComponent] :: ComponentDisabledReason [DisabledAllTests] :: ComponentDisabledReason [DisabledAllBenchmarks] :: ComponentDisabledReason -- | All the components in the package (libs, exes, or test suites). pkgComponents :: PackageDescription -> [Component] -- | All the components in the package that are buildable and enabled. Thus -- this excludes non-buildable components and test suites or benchmarks -- that have been disabled. pkgEnabledComponents :: PackageDescription -> [Component] lookupComponent :: PackageDescription -> ComponentName -> Maybe Component getComponent :: PackageDescription -> ComponentName -> Component getComponentLocalBuildInfo :: LocalBuildInfo -> ComponentName -> ComponentLocalBuildInfo allComponentsInBuildOrder :: LocalBuildInfo -> [(ComponentName, ComponentLocalBuildInfo)] componentsInBuildOrder :: LocalBuildInfo -> [ComponentName] -> [(ComponentName, ComponentLocalBuildInfo)] checkComponentsCyclic :: Ord key => [(node, key, [key])] -> Maybe [(node, key, [key])] -- | Determine the directories containing the dynamic libraries of the -- transitive dependencies of the component we are building. -- -- When wanted, and possible, returns paths relative to the installDirs -- prefix depLibraryPaths :: Bool -> Bool -> LocalBuildInfo -> ComponentLocalBuildInfo -> IO [FilePath] -- | Perform the action on each buildable Library or -- Executable (Component) in the PackageDescription, subject to -- the build order specified by the compBuildOrder field of the -- given LocalBuildInfo withAllComponentsInBuildOrder :: PackageDescription -> LocalBuildInfo -> (Component -> ComponentLocalBuildInfo -> IO ()) -> IO () withComponentsInBuildOrder :: PackageDescription -> LocalBuildInfo -> [ComponentName] -> (Component -> ComponentLocalBuildInfo -> IO ()) -> IO () -- | Deprecated: Use withAllComponentsInBuildOrder withComponentsLBI :: PackageDescription -> LocalBuildInfo -> (Component -> ComponentLocalBuildInfo -> IO ()) -> IO () -- | If the package description has a library section, call the given -- function with the library build info as argument. Extended version of -- withLib that also gives corresponding build info. withLibLBI :: PackageDescription -> LocalBuildInfo -> (Library -> ComponentLocalBuildInfo -> IO ()) -> IO () -- | Perform the action on each buildable Executable in the package -- description. Extended version of withExe that also gives -- corresponding build info. withExeLBI :: PackageDescription -> LocalBuildInfo -> (Executable -> ComponentLocalBuildInfo -> IO ()) -> IO () withTestLBI :: PackageDescription -> LocalBuildInfo -> (TestSuite -> ComponentLocalBuildInfo -> IO ()) -> IO () -- | See absoluteInstallDirs absoluteInstallDirs :: PackageDescription -> LocalBuildInfo -> CopyDest -> InstallDirs FilePath -- | See prefixRelativeInstallDirs prefixRelativeInstallDirs :: PackageId -> LocalBuildInfo -> InstallDirs (Maybe FilePath) substPathTemplate :: PackageId -> LocalBuildInfo -> PathTemplate -> FilePath instance Selector S1_0_27LocalBuildInfo instance Selector S1_0_26LocalBuildInfo instance Selector S1_0_25LocalBuildInfo instance Selector S1_0_24LocalBuildInfo instance Selector S1_0_23LocalBuildInfo instance Selector S1_0_22LocalBuildInfo instance Selector S1_0_21LocalBuildInfo instance Selector S1_0_20LocalBuildInfo instance Selector S1_0_19LocalBuildInfo instance Selector S1_0_18LocalBuildInfo instance Selector S1_0_17LocalBuildInfo instance Selector S1_0_16LocalBuildInfo instance Selector S1_0_15LocalBuildInfo instance Selector S1_0_14LocalBuildInfo instance Selector S1_0_13LocalBuildInfo instance Selector S1_0_12LocalBuildInfo instance Selector S1_0_11LocalBuildInfo instance Selector S1_0_10LocalBuildInfo instance Selector S1_0_9LocalBuildInfo instance Selector S1_0_8LocalBuildInfo instance Selector S1_0_7LocalBuildInfo instance Selector S1_0_6LocalBuildInfo instance Selector S1_0_5LocalBuildInfo instance Selector S1_0_4LocalBuildInfo instance Selector S1_0_3LocalBuildInfo instance Selector S1_0_2LocalBuildInfo instance Selector S1_0_1LocalBuildInfo instance Selector S1_0_0LocalBuildInfo instance Constructor C1_0LocalBuildInfo instance Datatype D1LocalBuildInfo instance Selector S1_3_1ComponentLocalBuildInfo instance Selector S1_3_0ComponentLocalBuildInfo instance Selector S1_2_1ComponentLocalBuildInfo instance Selector S1_2_0ComponentLocalBuildInfo instance Selector S1_1_1ComponentLocalBuildInfo instance Selector S1_1_0ComponentLocalBuildInfo instance Selector S1_0_3ComponentLocalBuildInfo instance Selector S1_0_2ComponentLocalBuildInfo instance Selector S1_0_1ComponentLocalBuildInfo instance Selector S1_0_0ComponentLocalBuildInfo instance Constructor C1_3ComponentLocalBuildInfo instance Constructor C1_2ComponentLocalBuildInfo instance Constructor C1_1ComponentLocalBuildInfo instance Constructor C1_0ComponentLocalBuildInfo instance Datatype D1ComponentLocalBuildInfo instance Constructor C1_0LibraryName instance Datatype D1LibraryName instance Constructor C1_3ComponentName instance Constructor C1_2ComponentName instance Constructor C1_1ComponentName instance Constructor C1_0ComponentName instance Datatype D1ComponentName instance Show LocalBuildInfo instance Read LocalBuildInfo instance Generic LocalBuildInfo instance Show ComponentLocalBuildInfo instance Read ComponentLocalBuildInfo instance Generic ComponentLocalBuildInfo instance Show LibraryName instance Read LibraryName instance Generic LibraryName instance Show ComponentName instance Read ComponentName instance Ord ComponentName instance Generic ComponentName instance Eq ComponentName instance Read Component instance Eq Component instance Show Component instance Binary LocalBuildInfo instance Binary ComponentName instance Binary ComponentLocalBuildInfo instance Binary LibraryName -- | A bunch of dirs, paths and file names used for intermediate build -- steps. module Distribution.Simple.BuildPaths defaultDistPref :: FilePath srcPref :: FilePath -> FilePath hscolourPref :: FilePath -> PackageDescription -> FilePath haddockPref :: FilePath -> PackageDescription -> FilePath -- | The directory in which we put auto-generated modules autogenModulesDir :: LocalBuildInfo -> String -- | The name of the auto-generated module associated with a package autogenModuleName :: PackageDescription -> ModuleName cppHeaderName :: String haddockName :: PackageDescription -> FilePath mkLibName :: LibraryName -> String mkProfLibName :: LibraryName -> String mkSharedLibName :: CompilerId -> LibraryName -> String -- | Extension for executable files (typically "" on Unix and -- "exe" on Windows or OS/2) exeExtension :: String -- | Extension for object files. For GHC the extension is "o". objExtension :: String -- | Extension for dynamically linked (or shared) libraries (typically -- "so" on Unix and "dll" on Windows) dllExtension :: String -- | Generating the Paths_pkgname module. -- -- This is a module that Cabal generates for the benefit of packages. It -- enables them to find their version number and find any installed data -- files at runtime. This code should probably be split off into another -- module. module Distribution.Simple.Build.PathsModule generate :: PackageDescription -> LocalBuildInfo -> String -- | Generates the name of the environment variable controlling the path -- component of interest. pkgPathEnvVar :: PackageDescription -> String -> String -- | Handling for user-specified build targets module Distribution.Simple.BuildTarget -- | A fully resolved build target. data BuildTarget -- | A specific component [BuildTargetComponent] :: ComponentName -> BuildTarget -- | A specific module within a specific component. [BuildTargetModule] :: ComponentName -> ModuleName -> BuildTarget -- | A specific file within a specific component. [BuildTargetFile] :: ComponentName -> FilePath -> BuildTarget readBuildTargets :: PackageDescription -> [String] -> IO [BuildTarget] -- | Various ways that a user may specify a build target. data UserBuildTarget readUserBuildTargets :: [String] -> ([UserBuildTargetProblem], [UserBuildTarget]) data UserBuildTargetProblem [UserBuildTargetUnrecognised] :: String -> UserBuildTargetProblem reportUserBuildTargetProblems :: [UserBuildTargetProblem] -> IO () -- | Given a bunch of user-specified targets, try to resolve what it is -- they refer to. resolveBuildTargets :: PackageDescription -> [(UserBuildTarget, Bool)] -> ([BuildTargetProblem], [BuildTarget]) data BuildTargetProblem -- | [BuildTargetExpected] :: UserBuildTarget -> [String] -> String -> BuildTargetProblem -- | [BuildTargetNoSuch] :: UserBuildTarget -> [(String, String)] -> BuildTargetProblem [BuildTargetAmbigious] :: UserBuildTarget -> [(UserBuildTarget, BuildTarget)] -> BuildTargetProblem reportBuildTargetProblems :: [BuildTargetProblem] -> IO () instance Show a => Show (MaybeAmbigious a) instance Show a => Show (Match a) instance Eq MatchError instance Show MatchError instance Show ComponentKind instance Ord ComponentKind instance Eq ComponentKind instance Show QualLevel instance Enum QualLevel instance Show BuildTargetProblem instance Show UserBuildTargetProblem instance Eq BuildTarget instance Show BuildTarget instance Ord UserBuildTarget instance Eq UserBuildTarget instance Show UserBuildTarget instance Alternative Match instance MonadPlus Match instance Functor Match instance Applicative Match instance Monad Match module Distribution.Simple.Test.Log -- | Logs all test results for a package, broken down first by test suite -- and then by test case. data PackageLog [PackageLog] :: PackageId -> CompilerId -> Platform -> [TestSuiteLog] -> PackageLog [package] :: PackageLog -> PackageId [compiler] :: PackageLog -> CompilerId [platform] :: PackageLog -> Platform [testSuites] :: PackageLog -> [TestSuiteLog] data TestLogs [TestLog] :: String -> Options -> Result -> TestLogs [testName] :: TestLogs -> String [testOptionsReturned] :: TestLogs -> Options [testResult] :: TestLogs -> Result [GroupLogs] :: String -> [TestLogs] -> TestLogs -- | Logs test suite results, itemized by test case. data TestSuiteLog [TestSuiteLog] :: String -> TestLogs -> FilePath -> TestSuiteLog [testSuiteName] :: TestSuiteLog -> String [testLogs] :: TestSuiteLog -> TestLogs [logFile] :: TestSuiteLog -> FilePath -- | Count the number of pass, fail, and error test results in a -- TestLogs tree. countTestResults :: TestLogs -> (Int, Int, Int) -- | A PackageLog with package and platform information specified. localPackageLog :: PackageDescription -> LocalBuildInfo -> PackageLog -- | Print a summary to the console after all test suites have been run -- indicating the number of successful test suites and cases. Returns -- True if all test suites passed and False otherwise. summarizePackage :: Verbosity -> PackageLog -> IO Bool -- | Print a summary of the test suite's results on the console, -- suppressing output for certain verbosity or test filter levels. summarizeSuiteFinish :: TestSuiteLog -> String summarizeSuiteStart :: String -> String -- | Print a summary of a single test case's result to the console, -- supressing output for certain verbosity or test filter levels. summarizeTest :: Verbosity -> TestShowDetails -> TestLogs -> IO () -- | From a TestSuiteLog, determine if the test suite encountered -- errors. suiteError :: TestLogs -> Bool -- | From a TestSuiteLog, determine if the test suite failed. suiteFailed :: TestLogs -> Bool -- | From a TestSuiteLog, determine if the test suite passed. suitePassed :: TestLogs -> Bool testSuiteLogPath :: PathTemplate -> PackageDescription -> LocalBuildInfo -> String -> TestLogs -> FilePath instance Eq PackageLog instance Show PackageLog instance Read PackageLog instance Eq TestSuiteLog instance Show TestSuiteLog instance Read TestSuiteLog instance Eq TestLogs instance Show TestLogs instance Read TestLogs -- | This module contains most of the JHC-specific code for configuring, -- building and installing packages. module Distribution.Simple.JHC configure :: Verbosity -> Maybe FilePath -> Maybe FilePath -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration) getInstalledPackages :: Verbosity -> PackageDBStack -> ProgramConfiguration -> IO InstalledPackageIndex -- | Building a package for JHC. Currently C source files are not -- supported. buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () -- | Building an executable for JHC. Currently C source files are not -- supported. buildExe :: Verbosity -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () installLib :: Verbosity -> FilePath -> FilePath -> PackageDescription -> Library -> IO () installExe :: Verbosity -> FilePath -> FilePath -> (FilePath, FilePath) -> PackageDescription -> Executable -> IO () -- | This is a fairly large module. It contains most of the GHC-specific -- code for configuring, building and installing packages. It also -- exports a function for finding out what packages are already -- installed. Configuring involves finding the ghc and -- ghc-pkg programs, finding what language extensions this -- version of ghc supports and returning a Compiler value. -- -- getInstalledPackages involves calling the ghc-pkg -- program to find out what packages are installed. -- -- Building is somewhat complex as there is quite a bit of information to -- take into account. We have to build libs and programs, possibly for -- profiling and shared libs. We have to support building libraries that -- will be usable by GHCi and also ghc's -split-objs feature. We -- have to compile any C files using ghc. Linking, especially for -- split-objs is remarkably complex, partly because there tend -- to be 1,000's of .o files and this can often be more than we -- can pass to the ld or ar programs in one go. -- -- Installing for libs and exes involves finding the right files and -- copying them to the right places. One of the more tricky things about -- this module is remembering the layout of files in the build directory -- (which is not explicitly documented) and thus what search dirs are -- used for various kinds of files. module Distribution.Simple.LHC configure :: Verbosity -> Maybe FilePath -> Maybe FilePath -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration) getInstalledPackages :: Verbosity -> PackageDBStack -> ProgramConfiguration -> IO InstalledPackageIndex -- | Build a library with LHC. buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () -- | Build an executable with LHC. buildExe :: Verbosity -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () -- | Install for ghc, .hi, .a and, if --with-ghci given, .o installLib :: Verbosity -> LocalBuildInfo -> FilePath -> FilePath -> FilePath -> PackageDescription -> Library -> ComponentLocalBuildInfo -> IO () -- | Install executables for GHC. installExe :: Verbosity -> LocalBuildInfo -> InstallDirs FilePath -> FilePath -> (FilePath, FilePath) -> PackageDescription -> Executable -> IO () registerPackage :: Verbosity -> InstalledPackageInfo -> PackageDescription -> LocalBuildInfo -> Bool -> PackageDBStack -> IO () hcPkgInfo :: ProgramConfiguration -> HcPkgInfo ghcOptions :: LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo -> FilePath -> [String] ghcVerbosityOptions :: Verbosity -> [String] -- | This module contains most of the UHC-specific code for configuring, -- building and installing packages. -- -- Thanks to the authors of the other implementation-specific files, in -- particular to Isaac Jones, Duncan Coutts and Henning Thielemann, for -- inspiration on how to design this module. module Distribution.Simple.UHC configure :: Verbosity -> Maybe FilePath -> Maybe FilePath -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration) getInstalledPackages :: Verbosity -> Compiler -> PackageDBStack -> ProgramConfiguration -> IO InstalledPackageIndex buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () buildExe :: Verbosity -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () installLib :: Verbosity -> LocalBuildInfo -> FilePath -> FilePath -> FilePath -> PackageDescription -> Library -> IO () registerPackage :: Verbosity -> InstalledPackageInfo -> PackageDescription -> LocalBuildInfo -> Bool -> PackageDBStack -> IO () module Distribution.Simple.HaskellSuite configure :: Verbosity -> Maybe FilePath -> Maybe FilePath -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration) hstoolVersion :: Verbosity -> FilePath -> IO (Maybe Version) numericVersion :: Verbosity -> FilePath -> IO (Maybe Version) getCompilerVersion :: Verbosity -> ConfiguredProgram -> IO (String, Version) getExtensions :: Verbosity -> ConfiguredProgram -> IO [(Extension, Flag)] getLanguages :: Verbosity -> ConfiguredProgram -> IO [(Language, Flag)] getInstalledPackages :: Verbosity -> PackageDBStack -> ProgramConfiguration -> IO InstalledPackageIndex buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () installLib :: Verbosity -> LocalBuildInfo -> FilePath -> FilePath -> FilePath -> PackageDescription -> Library -> IO () registerPackage :: Verbosity -> InstalledPackageInfo -> PackageDescription -> LocalBuildInfo -> Bool -> PackageDBStack -> IO () initPackageDB :: Verbosity -> ProgramConfiguration -> FilePath -> IO () packageDbOpt :: PackageDB -> String -- | This module provides functions for locating various HPC-related paths -- and a function for adding the necessary options to a -- PackageDescription to build test suites with HPC enabled. module Distribution.Simple.Hpc data Way [Vanilla] :: Way [Prof] :: Way [Dyn] :: Way -- | Attempt to guess the way the test suites in this package were compiled -- and linked with the library so the correct module interfaces are -- found. guessWay :: LocalBuildInfo -> Way htmlDir :: FilePath -> Way -> FilePath -> FilePath mixDir :: FilePath -> Way -> FilePath -> FilePath tixDir :: FilePath -> Way -> FilePath -> FilePath -- | Path to the .tix file containing a test suite's sum statistics. tixFilePath :: FilePath -> Way -> FilePath -> FilePath -- | Generate the HTML markup for all of a package's test suites. markupPackage :: Verbosity -> LocalBuildInfo -> FilePath -> String -> [TestSuite] -> IO () -- | Generate the HTML markup for a test suite. markupTest :: Verbosity -> LocalBuildInfo -> FilePath -> String -> TestSuite -> IO () instance Show Way instance Read Way instance Eq Way instance Enum Way instance Bounded Way -- | This module provides an library interface to the strip -- program. module Distribution.Simple.Program.Strip stripLib :: Verbosity -> Platform -> ProgramConfiguration -> FilePath -> IO () stripExe :: Verbosity -> Platform -> ProgramConfiguration -> FilePath -> IO () -- | This module provides an library interface to the ar program. module Distribution.Simple.Program.Ar -- | Call ar to create a library archive from a bunch of object -- files. createArLibArchive :: Verbosity -> LocalBuildInfo -> FilePath -> [FilePath] -> IO () -- | Like the unix xargs program. Useful for when we've got very long -- command lines that might overflow an OS limit on command line length -- and so you need to invoke a command multiple times to get all the args -- in. -- -- It takes four template invocations corresponding to the simple, -- initial, middle and last invocations. If the number of args given is -- small enough that we can get away with just a single invocation then -- the simple one is used: -- --
--   $ simple args
--   
-- -- If the number of args given means that we need to use multiple -- invocations then the templates for the initial, middle and last -- invocations are used: -- --
--   $ initial args_0
--   $ middle  args_1
--   $ middle  args_2
--     ...
--   $ final   args_n
--   
multiStageProgramInvocation :: ProgramInvocation -> (ProgramInvocation, ProgramInvocation, ProgramInvocation) -> [String] -> [ProgramInvocation] -- | This is a fairly large module. It contains most of the GHC-specific -- code for configuring, building and installing packages. It also -- exports a function for finding out what packages are already -- installed. Configuring involves finding the ghc and -- ghc-pkg programs, finding what language extensions this -- version of ghc supports and returning a Compiler value. -- -- getInstalledPackages involves calling the ghc-pkg -- program to find out what packages are installed. -- -- Building is somewhat complex as there is quite a bit of information to -- take into account. We have to build libs and programs, possibly for -- profiling and shared libs. We have to support building libraries that -- will be usable by GHCi and also ghc's -split-objs feature. We -- have to compile any C files using ghc. Linking, especially for -- split-objs is remarkably complex, partly because there tend -- to be 1,000's of .o files and this can often be more than we -- can pass to the ld or ar programs in one go. -- -- Installing for libs and exes involves finding the right files and -- copying them to the right places. One of the more tricky things about -- this module is remembering the layout of files in the build directory -- (which is not explicitly documented) and thus what search dirs are -- used for various kinds of files. module Distribution.Simple.GHC getGhcInfo :: Verbosity -> ConfiguredProgram -> IO [(String, String)] configure :: Verbosity -> Maybe FilePath -> Maybe FilePath -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration) -- | Given a package DB stack, return all installed packages. getInstalledPackages :: Verbosity -> PackageDBStack -> ProgramConfiguration -> IO InstalledPackageIndex -- | Given a single package DB, return all installed packages. getPackageDBContents :: Verbosity -> PackageDB -> ProgramConfiguration -> IO InstalledPackageIndex -- | Build a library with GHC. buildLib :: Verbosity -> Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () -- | Build an executable with GHC. buildExe :: Verbosity -> Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () -- | Build a library with GHC. replLib :: Verbosity -> Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () -- | Build an executable with GHC. replExe :: Verbosity -> Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () -- | Start a REPL without loading any source files. startInterpreter :: Verbosity -> ProgramConfiguration -> Compiler -> PackageDBStack -> IO () -- | Install for ghc, .hi, .a and, if --with-ghci given, .o installLib :: Verbosity -> LocalBuildInfo -> FilePath -> FilePath -> FilePath -> PackageDescription -> Library -> ComponentLocalBuildInfo -> IO () -- | Install executables for GHC. installExe :: Verbosity -> LocalBuildInfo -> InstallDirs FilePath -> FilePath -> (FilePath, FilePath) -> PackageDescription -> Executable -> IO () -- | Extracts a String representing a hash of the ABI of a built library. -- It can fail if the library has not yet been built. libAbiHash :: Verbosity -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO String hcPkgInfo :: ProgramConfiguration -> HcPkgInfo registerPackage :: Verbosity -> InstalledPackageInfo -> PackageDescription -> LocalBuildInfo -> Bool -> PackageDBStack -> IO () componentGhcOptions :: Verbosity -> LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo -> FilePath -> GhcOptions getLibDir :: Verbosity -> LocalBuildInfo -> IO FilePath isDynamic :: Compiler -> Bool -- | Return the FilePath to the global GHC package database. getGlobalPackageDB :: Verbosity -> ConfiguredProgram -> IO FilePath pkgRoot :: Verbosity -> LocalBuildInfo -> PackageDB -> IO FilePath module Distribution.Simple.GHCJS configure :: Verbosity -> Maybe FilePath -> Maybe FilePath -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration) -- | Given a package DB stack, return all installed packages. getInstalledPackages :: Verbosity -> PackageDBStack -> ProgramConfiguration -> IO InstalledPackageIndex -- | Given a single package DB, return all installed packages. getPackageDBContents :: Verbosity -> PackageDB -> ProgramConfiguration -> IO InstalledPackageIndex buildLib :: Verbosity -> Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () buildExe :: Verbosity -> Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () replLib :: Verbosity -> Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () replExe :: Verbosity -> Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () -- | Start a REPL without loading any source files. startInterpreter :: Verbosity -> ProgramConfiguration -> Compiler -> PackageDBStack -> IO () -- | Install for ghc, .hi, .a and, if --with-ghci given, .o installLib :: Verbosity -> LocalBuildInfo -> FilePath -> FilePath -> FilePath -> PackageDescription -> Library -> ComponentLocalBuildInfo -> IO () installExe :: Verbosity -> LocalBuildInfo -> InstallDirs FilePath -> FilePath -> (FilePath, FilePath) -> PackageDescription -> Executable -> IO () libAbiHash :: Verbosity -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO String hcPkgInfo :: ProgramConfiguration -> HcPkgInfo registerPackage :: Verbosity -> InstalledPackageInfo -> PackageDescription -> LocalBuildInfo -> Bool -> PackageDBStack -> IO () componentGhcOptions :: Verbosity -> LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo -> FilePath -> GhcOptions getLibDir :: Verbosity -> LocalBuildInfo -> IO FilePath isDynamic :: Compiler -> Bool -- | Return the FilePath to the global GHC package database. getGlobalPackageDB :: Verbosity -> ConfiguredProgram -> IO FilePath -- | Get the JavaScript file name and command and arguments to run a -- program compiled by GHCJS the exe should be the base program name -- without exe extension runCmd :: ProgramConfiguration -> FilePath -> (FilePath, FilePath, [String]) -- | This module deals with registering and unregistering packages. There -- are a couple ways it can do this, one is to do it directly. Another is -- to generate a script that can be run later to do it. The idea here -- being that the user is shielded from the details of what command to -- use for package registration for a particular compiler. In practice -- this aspect was not especially popular so we also provide a way to -- simply generate the package registration file which then must be -- manually passed to ghc-pkg. It is possible to generate -- registration information for where the package is to be installed, or -- alternatively to register the package in place in the build tree. The -- latter is occasionally handy, and will become more important when we -- try to build multi-package systems. -- -- This module does not delegate anything to the per-compiler modules but -- just mixes it all in in this module, which is rather unsatisfactory. -- The script generation and the unregister feature are not well used or -- tested. module Distribution.Simple.Register register :: PackageDescription -> LocalBuildInfo -> RegisterFlags -> IO () unregister :: PackageDescription -> LocalBuildInfo -> RegisterFlags -> IO () -- | Create an empty package DB at the specified location. initPackageDB :: Verbosity -> Compiler -> ProgramConfiguration -> FilePath -> IO () -- | Run hc-pkg using a given package DB stack, directly -- forwarding the provided command-line arguments to it. invokeHcPkg :: Verbosity -> Compiler -> ProgramConfiguration -> PackageDBStack -> [String] -> IO () registerPackage :: Verbosity -> InstalledPackageInfo -> PackageDescription -> LocalBuildInfo -> Bool -> PackageDBStack -> IO () generateRegistrationInfo :: Verbosity -> PackageDescription -> Library -> LocalBuildInfo -> ComponentLocalBuildInfo -> Bool -> Bool -> FilePath -> PackageDB -> IO InstalledPackageInfo -- | Construct InstalledPackageInfo for a library that is in place -- in the build tree. -- -- This function knows about the layout of in place packages. inplaceInstalledPackageInfo :: FilePath -> FilePath -> PackageDescription -> InstalledPackageId -> Library -> LocalBuildInfo -> ComponentLocalBuildInfo -> InstalledPackageInfo -- | Construct InstalledPackageInfo for the final install location -- of a library package. -- -- This function knows about the layout of installed packages. absoluteInstalledPackageInfo :: PackageDescription -> InstalledPackageId -> Library -> LocalBuildInfo -> ComponentLocalBuildInfo -> InstalledPackageInfo -- | Construct InstalledPackageInfo for a library in a package, -- given a set of installation directories. generalInstalledPackageInfo :: ([FilePath] -> [FilePath]) -> PackageDescription -> InstalledPackageId -> Library -> LocalBuildInfo -> ComponentLocalBuildInfo -> InstallDirs FilePath -> InstalledPackageInfo -- | This is the entry point into installing a built package. Performs the -- "./setup install" and "./setup copy" actions. It -- moves files into place based on the prefix argument. It does the -- generic bits and then calls compiler-specific functions to do the -- rest. module Distribution.Simple.Install -- | Perform the "./setup install" and "./setup copy" -- actions. Move files into place based on the prefix argument. install :: PackageDescription -> LocalBuildInfo -> CopyFlags -> IO () -- | Generate cabal_macros.h - CPP macros for package version testing -- -- When using CPP you get -- --
--   VERSION_<package>
--   MIN_VERSION_<package>(A,B,C)
--   
-- -- for each package in build-depends, which is true if -- the version of package in use is >= A.B.C, using -- the normal ordering on version numbers. module Distribution.Simple.Build.Macros -- | The contents of the cabal_macros.h for the given configured -- package. generate :: PackageDescription -> LocalBuildInfo -> String -- | Helper function that generates just the VERSION_pkg and -- MIN_VERSION_pkg macros for a list of package ids (usually -- used with the specific deps of a configured package). generatePackageVersionMacros :: [PackageIdentifier] -> String module Distribution.Compat.CreatePipe createPipe :: IO (Handle, Handle) module Distribution.Simple.Test.LibV09 runTest :: PackageDescription -> LocalBuildInfo -> TestFlags -> TestSuite -> IO TestSuiteLog -- | Source code for library test suite stub executable simpleTestStub :: ModuleName -> String -- | The filename of the source file for the stub executable associated -- with a library TestSuite. stubFilePath :: TestSuite -> FilePath -- | Main function for test stubs. Once, it was written directly into the -- stub, but minimizing the amount of code actually in the stub maximizes -- the number of detectable errors when Cabal is compiled. stubMain :: IO [Test] -> IO () -- | The name of the stub executable associated with a library -- TestSuite. stubName :: TestSuite -> FilePath -- | From a test stub, write the TestSuiteLog to temporary file for -- the calling Cabal process to read. stubWriteLog :: FilePath -> String -> TestLogs -> IO () -- | Write the source file for a library TestSuite stub -- executable. writeSimpleTestStub :: TestSuite -> FilePath -> IO () -- | This defines a PreProcessor abstraction which represents a -- pre-processor that can transform one kind of file into another. There -- is also a PPSuffixHandler which is a combination of a file -- extension and a function for configuring a PreProcessor. It -- defines a bunch of known built-in preprocessors like cpp, -- cpphs, c2hs, hsc2hs, happy, -- alex etc and lists them in knownSuffixHandlers. On top -- of this it provides a function for actually preprocessing some sources -- given a bunch of known suffix handlers. This module is not as good as -- it could be, it could really do with a rewrite to address some of the -- problems we have with pre-processors. module Distribution.Simple.PreProcess -- | Apply preprocessors to the sources from hsSourceDirs for a -- given component (lib, exe, or test suite). preprocessComponent :: PackageDescription -> Component -> LocalBuildInfo -> Bool -> Verbosity -> [PPSuffixHandler] -> IO () -- | Standard preprocessors: GreenCard, c2hs, hsc2hs, happy, alex and -- cpphs. knownSuffixHandlers :: [PPSuffixHandler] -- | Convenience function; get the suffixes of these preprocessors. ppSuffixes :: [PPSuffixHandler] -> [String] -- | A preprocessor for turning non-Haskell files with the given extension -- into plain Haskell source files. type PPSuffixHandler = (String, BuildInfo -> LocalBuildInfo -> PreProcessor) -- | The interface to a preprocessor, which may be implemented using an -- external program, but need not be. The arguments are the name of the -- input file, the name of the output file and a verbosity level. Here is -- a simple example that merely prepends a comment to the given source -- file: -- --
--   ppTestHandler :: PreProcessor
--   ppTestHandler =
--     PreProcessor {
--       platformIndependent = True,
--       runPreProcessor = mkSimplePreProcessor $ \inFile outFile verbosity ->
--         do info verbosity (inFile++" has been preprocessed to "++outFile)
--            stuff <- readFile inFile
--            writeFile outFile ("-- preprocessed as a test\n\n" ++ stuff)
--            return ExitSuccess
--   
-- -- We split the input and output file names into a base directory and the -- rest of the file name. The input base dir is the path in the list of -- search dirs that this file was found in. The output base dir is the -- build dir where all the generated source files are put. -- -- The reason for splitting it up this way is that some pre-processors -- don't simply generate one output .hs file from one input file but have -- dependencies on other generated files (notably c2hs, where building -- one .hs file may require reading other .chi files, and then compiling -- the .hs file may require reading a generated .h file). In these cases -- the generated files need to embed relative path names to each other -- (eg the generated .hs file mentions the .h file in the FFI imports). -- This path must be relative to the base directory where the generated -- files are located, it cannot be relative to the top level of the build -- tree because the compilers do not look for .h files relative to there, -- ie we do not use "-I .", instead we use "-I dist/build" (or whatever -- dist dir has been set by the user) -- -- Most pre-processors do not care of course, so mkSimplePreProcessor and -- runSimplePreProcessor functions handle the simple case. data PreProcessor [PreProcessor] :: Bool -> ((FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO ()) -> PreProcessor [platformIndependent] :: PreProcessor -> Bool [runPreProcessor] :: PreProcessor -> (FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO () mkSimplePreProcessor :: (FilePath -> FilePath -> Verbosity -> IO ()) -> (FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO () runSimplePreProcessor :: PreProcessor -> FilePath -> FilePath -> Verbosity -> IO () ppCpp :: BuildInfo -> LocalBuildInfo -> PreProcessor ppCpp' :: [String] -> BuildInfo -> LocalBuildInfo -> PreProcessor ppGreenCard :: BuildInfo -> LocalBuildInfo -> PreProcessor ppC2hs :: BuildInfo -> LocalBuildInfo -> PreProcessor ppHsc2hs :: BuildInfo -> LocalBuildInfo -> PreProcessor ppHappy :: BuildInfo -> LocalBuildInfo -> PreProcessor ppAlex :: BuildInfo -> LocalBuildInfo -> PreProcessor ppUnlit :: PreProcessor platformDefines :: LocalBuildInfo -> [String] -- | This defines the API that Setup.hs scripts can use to -- customise the way the build works. This module just defines the -- UserHooks type. The predefined sets of hooks that implement the -- Simple, Make and Configure build systems -- are defined in Distribution.Simple. The UserHooks is a -- big record of functions. There are 3 for each action, a pre, post and -- the action itself. There are few other miscellaneous hooks, ones to -- extend the set of programs and preprocessors and one to override the -- function used to read the .cabal file. -- -- This hooks type is widely agreed to not be the right solution. Partly -- this is because changes to it usually break custom Setup.hs -- files and yet many internal code changes do require changes to the -- hooks. For example we cannot pass any extra parameters to most of the -- functions that implement the various phases because it would involve -- changing the types of the corresponding hook. At some point it will -- have to be replaced. module Distribution.Simple.UserHooks -- | Hooks allow authors to add specific functionality before and after a -- command is run, and also to specify additional preprocessors. -- -- data UserHooks [UserHooks] :: (Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO ()) -> IO (Maybe GenericPackageDescription) -> [PPSuffixHandler] -> [Program] -> (Args -> ConfigFlags -> IO HookedBuildInfo) -> ((GenericPackageDescription, HookedBuildInfo) -> ConfigFlags -> IO LocalBuildInfo) -> (Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> BuildFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()) -> (Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> ReplFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO ()) -> (Args -> ReplFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> CleanFlags -> IO HookedBuildInfo) -> (PackageDescription -> () -> UserHooks -> CleanFlags -> IO ()) -> (Args -> CleanFlags -> PackageDescription -> () -> IO ()) -> (Args -> CopyFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()) -> (Args -> CopyFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> InstallFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()) -> (Args -> InstallFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> SDistFlags -> IO HookedBuildInfo) -> (PackageDescription -> Maybe LocalBuildInfo -> UserHooks -> SDistFlags -> IO ()) -> (Args -> SDistFlags -> PackageDescription -> Maybe LocalBuildInfo -> IO ()) -> (Args -> RegisterFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()) -> (Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> RegisterFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()) -> (Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> HscolourFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()) -> (Args -> HscolourFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> HaddockFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()) -> (Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> TestFlags -> IO HookedBuildInfo) -> (Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> TestFlags -> IO ()) -> (Args -> TestFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> BenchmarkFlags -> IO HookedBuildInfo) -> (Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> BenchmarkFlags -> IO ()) -> (Args -> BenchmarkFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> UserHooks -- | Used for ./setup test -- | Deprecated: Please use the new testing interface instead! [runTests] :: UserHooks -> Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO () -- | Read the description file [readDesc] :: UserHooks -> IO (Maybe GenericPackageDescription) -- | Custom preprocessors in addition to and overriding -- knownSuffixHandlers. [hookedPreProcessors] :: UserHooks -> [PPSuffixHandler] -- | These programs are detected at configure time. Arguments for them are -- added to the configure command. [hookedPrograms] :: UserHooks -> [Program] -- | Hook to run before configure command [preConf] :: UserHooks -> Args -> ConfigFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during configure. [confHook] :: UserHooks -> (GenericPackageDescription, HookedBuildInfo) -> ConfigFlags -> IO LocalBuildInfo -- | Hook to run after configure command [postConf] :: UserHooks -> Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before build command. Second arg indicates verbosity -- level. [preBuild] :: UserHooks -> Args -> BuildFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during build. [buildHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO () -- | Hook to run after build command. Second arg indicates verbosity level. [postBuild] :: UserHooks -> Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before repl command. Second arg indicates verbosity level. [preRepl] :: UserHooks -> Args -> ReplFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during interpretation. [replHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO () -- | Hook to run after repl command. Second arg indicates verbosity level. [postRepl] :: UserHooks -> Args -> ReplFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before clean command. Second arg indicates verbosity -- level. [preClean] :: UserHooks -> Args -> CleanFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during clean. [cleanHook] :: UserHooks -> PackageDescription -> () -> UserHooks -> CleanFlags -> IO () -- | Hook to run after clean command. Second arg indicates verbosity level. [postClean] :: UserHooks -> Args -> CleanFlags -> PackageDescription -> () -> IO () -- | Hook to run before copy command [preCopy] :: UserHooks -> Args -> CopyFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during copy. [copyHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO () -- | Hook to run after copy command [postCopy] :: UserHooks -> Args -> CopyFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before install command [preInst] :: UserHooks -> Args -> InstallFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during install. [instHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO () -- | Hook to run after install command. postInst should be run on the -- target, not on the build machine. [postInst] :: UserHooks -> Args -> InstallFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before sdist command. Second arg indicates verbosity -- level. [preSDist] :: UserHooks -> Args -> SDistFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during sdist. [sDistHook] :: UserHooks -> PackageDescription -> Maybe LocalBuildInfo -> UserHooks -> SDistFlags -> IO () -- | Hook to run after sdist command. Second arg indicates verbosity level. [postSDist] :: UserHooks -> Args -> SDistFlags -> PackageDescription -> Maybe LocalBuildInfo -> IO () -- | Hook to run before register command [preReg] :: UserHooks -> Args -> RegisterFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during registration. [regHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO () -- | Hook to run after register command [postReg] :: UserHooks -> Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before unregister command [preUnreg] :: UserHooks -> Args -> RegisterFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during unregistration. [unregHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO () -- | Hook to run after unregister command [postUnreg] :: UserHooks -> Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before hscolour command. Second arg indicates verbosity -- level. [preHscolour] :: UserHooks -> Args -> HscolourFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during hscolour. [hscolourHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO () -- | Hook to run after hscolour command. Second arg indicates verbosity -- level. [postHscolour] :: UserHooks -> Args -> HscolourFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before haddock command. Second arg indicates verbosity -- level. [preHaddock] :: UserHooks -> Args -> HaddockFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during haddock. [haddockHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO () -- | Hook to run after haddock command. Second arg indicates verbosity -- level. [postHaddock] :: UserHooks -> Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before test command. [preTest] :: UserHooks -> Args -> TestFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during test. [testHook] :: UserHooks -> Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> TestFlags -> IO () -- | Hook to run after test command. [postTest] :: UserHooks -> Args -> TestFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before bench command. [preBench] :: UserHooks -> Args -> BenchmarkFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during bench. [benchHook] :: UserHooks -> Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> BenchmarkFlags -> IO () -- | Hook to run after bench command. [postBench] :: UserHooks -> Args -> BenchmarkFlags -> PackageDescription -> LocalBuildInfo -> IO () type Args = [String] -- | Empty UserHooks which do nothing. emptyUserHooks :: UserHooks -- | This is the entry point into running the benchmarks in a built -- package. It performs the "./setup bench" action. It runs -- benchmarks designated in the package description. module Distribution.Simple.Bench -- | Perform the "./setup bench" action. bench :: Args -> PackageDescription -> LocalBuildInfo -> BenchmarkFlags -> IO () -- | This handles the sdist command. The module exports an -- sdist action but also some of the phases that make it up so -- that other tools can use just the bits they need. In particular the -- preparation of the tree of files to go into the source tarball is -- separated from actually building the source tarball. -- -- The createArchive action uses the external tar program -- and assumes that it accepts the -z flag. Neither of these -- assumptions are valid on Windows. The sdist action now also -- does some distribution QA checks. module Distribution.Simple.SrcDist -- | Create a source distribution. sdist :: PackageDescription -> Maybe LocalBuildInfo -> SDistFlags -> (FilePath -> FilePath) -> [PPSuffixHandler] -> IO () printPackageProblems :: Verbosity -> PackageDescription -> IO () -- | Prepare a directory tree of source files. prepareTree :: Verbosity -> PackageDescription -> Maybe LocalBuildInfo -> FilePath -> [PPSuffixHandler] -> IO () -- | Create an archive from a tree of source files, and clean up the tree. createArchive :: CreateArchiveFun -- | Prepare a directory tree of source files for a snapshot version. It is -- expected that the appropriate snapshot version has already been set in -- the package description, eg using snapshotPackage or -- snapshotVersion. prepareSnapshotTree :: Verbosity -> PackageDescription -> Maybe LocalBuildInfo -> FilePath -> [PPSuffixHandler] -> IO () -- | Modifies a PackageDescription by appending a snapshot number -- corresponding to the given date. snapshotPackage :: UTCTime -> PackageDescription -> PackageDescription -- | Modifies a Version by appending a snapshot number corresponding -- to the given date. snapshotVersion :: UTCTime -> Version -> Version -- | Given a date produce a corresponding integer representation. For -- example given a date 18032008 produce the number -- 20080318. dateToSnapshotNumber :: UTCTime -> Int -- | List all source files of a package. Returns a tuple of lists: first -- component is a list of ordinary files, second one is a list of those -- files that may be executable. listPackageSources :: Verbosity -> PackageDescription -> [PPSuffixHandler] -> IO ([FilePath], [FilePath]) -- | This deals with the configure phase. It provides the -- configure action which is given the package description and -- configure flags. It then tries to: configure the compiler; resolves -- any conditionals in the package description; resolve the package -- dependencies; check if all the extensions used by this package are -- supported by the compiler; check that all the build tools are -- available (including version checks if appropriate); checks for any -- required pkg-config packages (updating the BuildInfo -- with the results) -- -- Then based on all this it saves the info in the LocalBuildInfo -- and writes it out to the dist/setup-config file. It also -- displays various details to the user, the amount of information -- displayed depending on the verbosity level. module Distribution.Simple.Configure -- | Perform the "./setup configure" action. Returns the -- .setup-config file. configure :: (GenericPackageDescription, HookedBuildInfo) -> ConfigFlags -> IO LocalBuildInfo -- | After running configure, output the LocalBuildInfo to the -- localBuildInfoFile. writePersistBuildConfig :: FilePath -> LocalBuildInfo -> IO () getConfigStateFile :: FilePath -> IO LocalBuildInfo -- | Read the localBuildInfoFile. Throw an exception if the file is -- missing, if the file cannot be read, or if the file was created by an -- older version of Cabal. getPersistBuildConfig :: FilePath -> IO LocalBuildInfo -- | Check that localBuildInfoFile is up-to-date with respect to the .cabal -- file. checkPersistBuildConfigOutdated :: FilePath -> FilePath -> IO Bool -- | Try to read the localBuildInfoFile. tryGetPersistBuildConfig :: FilePath -> IO (Either ConfigStateFileError LocalBuildInfo) -- | Try to read the localBuildInfoFile. maybeGetPersistBuildConfig :: FilePath -> IO (Maybe LocalBuildInfo) -- |
--   dist/setup-config
--   
localBuildInfoFile :: FilePath -> FilePath getInstalledPackages :: Verbosity -> Compiler -> PackageDBStack -> ProgramConfiguration -> IO InstalledPackageIndex -- | Like getInstalledPackages, but for a single package DB. getPackageDBContents :: Verbosity -> Compiler -> PackageDB -> ProgramConfiguration -> IO InstalledPackageIndex -- | Deprecated: configCompiler is deprecated. Use -- configCompilerEx instead. configCompiler :: Maybe CompilerFlavor -> Maybe FilePath -> Maybe FilePath -> ProgramConfiguration -> Verbosity -> IO (Compiler, ProgramConfiguration) -- | Deprecated: configCompilerAux is deprecated. Use -- configCompilerAuxEx instead. configCompilerAux :: ConfigFlags -> IO (Compiler, ProgramConfiguration) configCompilerEx :: Maybe CompilerFlavor -> Maybe FilePath -> Maybe FilePath -> ProgramConfiguration -> Verbosity -> IO (Compiler, Platform, ProgramConfiguration) configCompilerAuxEx :: ConfigFlags -> IO (Compiler, Platform, ProgramConfiguration) -- | Makes a BuildInfo from C compiler and linker flags. -- -- This can be used with the output from configuration programs like -- pkg-config and similar package-specific programs like mysql-config, -- freealut-config etc. For example: -- --
--   ccflags <- rawSystemProgramStdoutConf verbosity prog conf ["--cflags"]
--   ldflags <- rawSystemProgramStdoutConf verbosity prog conf ["--libs"]
--   return (ccldOptionsBuildInfo (words ccflags) (words ldflags))
--   
ccLdOptionsBuildInfo :: [String] -> [String] -> BuildInfo checkForeignDeps :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO () -- | The user interface specifies the package dbs to use with a combination -- of --global, --user and -- --package-db=global|user|clear|$file. This function combines -- the global/user flag and interprets the package-db flag into a single -- package db stack. interpretPackageDbFlags :: Bool -> [Maybe PackageDB] -> PackageDBStack data ConfigStateFileError [ConfigStateFileNoHeader] :: ConfigStateFileError [ConfigStateFileBadHeader] :: ConfigStateFileError [ConfigStateFileNoParse] :: ConfigStateFileError [ConfigStateFileMissing] :: ConfigStateFileError [ConfigStateFileBadVersion] :: PackageIdentifier -> PackageIdentifier -> (Either ConfigStateFileError LocalBuildInfo) -> ConfigStateFileError tryGetConfigStateFile :: FilePath -> IO (Either ConfigStateFileError LocalBuildInfo) platformDefines :: LocalBuildInfo -> [String] instance Show ConfigStateFileError instance Exception ConfigStateFileError -- | This is the entry point to actually building the modules in a package. -- It doesn't actually do much itself, most of the work is delegated to -- compiler-specific actions. It does do some non-compiler specific bits -- like running pre-processors. module Distribution.Simple.Build -- | Build the libraries and executables in this package. build :: PackageDescription -> LocalBuildInfo -> BuildFlags -> [PPSuffixHandler] -> IO () repl :: PackageDescription -> LocalBuildInfo -> ReplFlags -> [PPSuffixHandler] -> [String] -> IO () -- | Start an interpreter without loading any package files. startInterpreter :: Verbosity -> ProgramDb -> Compiler -> PackageDBStack -> IO () initialBuildSteps :: FilePath -> PackageDescription -> LocalBuildInfo -> Verbosity -> IO () -- | Generate and write out the Paths_pkg.hs and cabal_macros.h -- files writeAutogenFiles :: Verbosity -> PackageDescription -> LocalBuildInfo -> IO () -- | This module deals with the haddock and hscolour -- commands. It uses information about installed packages (from -- ghc-pkg) to find the locations of documentation for dependent -- packages, so it can create links. -- -- The hscolour support allows generating HTML versions of the -- original source, with coloured syntax highlighting. module Distribution.Simple.Haddock haddock :: PackageDescription -> LocalBuildInfo -> [PPSuffixHandler] -> HaddockFlags -> IO () hscolour :: PackageDescription -> LocalBuildInfo -> [PPSuffixHandler] -> HscolourFlags -> IO () -- | Given a list of InstalledPackageInfos, return a list of -- interfaces and HTML paths, and an optional warning for packages with -- missing documentation. haddockPackagePaths :: [InstalledPackageInfo] -> Maybe (InstalledPackageInfo -> FilePath) -> IO ([(FilePath, Maybe FilePath)], Maybe String) instance Ord Directory instance Eq Directory instance Show Directory instance Read Directory instance Monoid HaddockArgs instance Monoid Directory module Distribution.Simple.Test.ExeV10 runTest :: PackageDescription -> LocalBuildInfo -> TestFlags -> TestSuite -> IO TestSuiteLog -- | This is the entry point into testing a built package. It performs the -- "./setup test" action. It runs test suites designated in the -- package description and reports on the results. module Distribution.Simple.Test -- | Perform the "./setup test" action. test :: Args -> PackageDescription -> LocalBuildInfo -> TestFlags -> IO () -- | This is the command line front end to the Simple build system. When -- given the parsed command-line args and package information, is able to -- perform basic commands like configure, build, install, register, etc. -- -- This module exports the main functions that Setup.hs scripts use. It -- re-exports the UserHooks type, the standard entry points like -- defaultMain and defaultMainWithHooks and the predefined -- sets of UserHooks that custom Setup.hs scripts can -- extend to add their own behaviour. -- -- This module isn't called "Simple" because it's simple. Far from it. -- It's called "Simple" because it does complicated things to simple -- software. -- -- The original idea was that there could be different build systems that -- all presented the same compatible command line interfaces. There is -- still a Distribution.Make system but in practice no packages -- use it. module Distribution.Simple -- | A simple implementation of main for a Cabal setup script. It -- reads the package description file using IO, and performs the action -- specified on the command line. defaultMain :: IO () -- | Like defaultMain, but accepts the package description as input -- rather than using IO to read it. defaultMainNoRead :: GenericPackageDescription -> IO () -- | A version of defaultMain that is passed the command line -- arguments, rather than getting them from the environment. defaultMainArgs :: [String] -> IO () -- | Hooks allow authors to add specific functionality before and after a -- command is run, and also to specify additional preprocessors. -- -- data UserHooks [UserHooks] :: (Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO ()) -> IO (Maybe GenericPackageDescription) -> [PPSuffixHandler] -> [Program] -> (Args -> ConfigFlags -> IO HookedBuildInfo) -> ((GenericPackageDescription, HookedBuildInfo) -> ConfigFlags -> IO LocalBuildInfo) -> (Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> BuildFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()) -> (Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> ReplFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO ()) -> (Args -> ReplFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> CleanFlags -> IO HookedBuildInfo) -> (PackageDescription -> () -> UserHooks -> CleanFlags -> IO ()) -> (Args -> CleanFlags -> PackageDescription -> () -> IO ()) -> (Args -> CopyFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()) -> (Args -> CopyFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> InstallFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()) -> (Args -> InstallFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> SDistFlags -> IO HookedBuildInfo) -> (PackageDescription -> Maybe LocalBuildInfo -> UserHooks -> SDistFlags -> IO ()) -> (Args -> SDistFlags -> PackageDescription -> Maybe LocalBuildInfo -> IO ()) -> (Args -> RegisterFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()) -> (Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> RegisterFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()) -> (Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> HscolourFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()) -> (Args -> HscolourFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> HaddockFlags -> IO HookedBuildInfo) -> (PackageDescription -> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()) -> (Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> TestFlags -> IO HookedBuildInfo) -> (Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> TestFlags -> IO ()) -> (Args -> TestFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> (Args -> BenchmarkFlags -> IO HookedBuildInfo) -> (Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> BenchmarkFlags -> IO ()) -> (Args -> BenchmarkFlags -> PackageDescription -> LocalBuildInfo -> IO ()) -> UserHooks -- | Used for ./setup test -- | Deprecated: Please use the new testing interface instead! [runTests] :: UserHooks -> Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO () -- | Read the description file [readDesc] :: UserHooks -> IO (Maybe GenericPackageDescription) -- | Custom preprocessors in addition to and overriding -- knownSuffixHandlers. [hookedPreProcessors] :: UserHooks -> [PPSuffixHandler] -- | These programs are detected at configure time. Arguments for them are -- added to the configure command. [hookedPrograms] :: UserHooks -> [Program] -- | Hook to run before configure command [preConf] :: UserHooks -> Args -> ConfigFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during configure. [confHook] :: UserHooks -> (GenericPackageDescription, HookedBuildInfo) -> ConfigFlags -> IO LocalBuildInfo -- | Hook to run after configure command [postConf] :: UserHooks -> Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before build command. Second arg indicates verbosity -- level. [preBuild] :: UserHooks -> Args -> BuildFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during build. [buildHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO () -- | Hook to run after build command. Second arg indicates verbosity level. [postBuild] :: UserHooks -> Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before repl command. Second arg indicates verbosity level. [preRepl] :: UserHooks -> Args -> ReplFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during interpretation. [replHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO () -- | Hook to run after repl command. Second arg indicates verbosity level. [postRepl] :: UserHooks -> Args -> ReplFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before clean command. Second arg indicates verbosity -- level. [preClean] :: UserHooks -> Args -> CleanFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during clean. [cleanHook] :: UserHooks -> PackageDescription -> () -> UserHooks -> CleanFlags -> IO () -- | Hook to run after clean command. Second arg indicates verbosity level. [postClean] :: UserHooks -> Args -> CleanFlags -> PackageDescription -> () -> IO () -- | Hook to run before copy command [preCopy] :: UserHooks -> Args -> CopyFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during copy. [copyHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO () -- | Hook to run after copy command [postCopy] :: UserHooks -> Args -> CopyFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before install command [preInst] :: UserHooks -> Args -> InstallFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during install. [instHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO () -- | Hook to run after install command. postInst should be run on the -- target, not on the build machine. [postInst] :: UserHooks -> Args -> InstallFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before sdist command. Second arg indicates verbosity -- level. [preSDist] :: UserHooks -> Args -> SDistFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during sdist. [sDistHook] :: UserHooks -> PackageDescription -> Maybe LocalBuildInfo -> UserHooks -> SDistFlags -> IO () -- | Hook to run after sdist command. Second arg indicates verbosity level. [postSDist] :: UserHooks -> Args -> SDistFlags -> PackageDescription -> Maybe LocalBuildInfo -> IO () -- | Hook to run before register command [preReg] :: UserHooks -> Args -> RegisterFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during registration. [regHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO () -- | Hook to run after register command [postReg] :: UserHooks -> Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before unregister command [preUnreg] :: UserHooks -> Args -> RegisterFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during unregistration. [unregHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO () -- | Hook to run after unregister command [postUnreg] :: UserHooks -> Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before hscolour command. Second arg indicates verbosity -- level. [preHscolour] :: UserHooks -> Args -> HscolourFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during hscolour. [hscolourHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO () -- | Hook to run after hscolour command. Second arg indicates verbosity -- level. [postHscolour] :: UserHooks -> Args -> HscolourFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before haddock command. Second arg indicates verbosity -- level. [preHaddock] :: UserHooks -> Args -> HaddockFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during haddock. [haddockHook] :: UserHooks -> PackageDescription -> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO () -- | Hook to run after haddock command. Second arg indicates verbosity -- level. [postHaddock] :: UserHooks -> Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before test command. [preTest] :: UserHooks -> Args -> TestFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during test. [testHook] :: UserHooks -> Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> TestFlags -> IO () -- | Hook to run after test command. [postTest] :: UserHooks -> Args -> TestFlags -> PackageDescription -> LocalBuildInfo -> IO () -- | Hook to run before bench command. [preBench] :: UserHooks -> Args -> BenchmarkFlags -> IO HookedBuildInfo -- | Over-ride this hook to get different behavior during bench. [benchHook] :: UserHooks -> Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> BenchmarkFlags -> IO () -- | Hook to run after bench command. [postBench] :: UserHooks -> Args -> BenchmarkFlags -> PackageDescription -> LocalBuildInfo -> IO () type Args = [String] -- | A customizable version of defaultMain. defaultMainWithHooks :: UserHooks -> IO () -- | A customizable version of defaultMain that also takes the -- command line arguments. defaultMainWithHooksArgs :: UserHooks -> [String] -> IO () -- | Hooks that correspond to a plain instantiation of the "simple" build -- system simpleUserHooks :: UserHooks autoconfUserHooks :: UserHooks -- | Basic autoconf UserHooks: -- -- -- -- Thus configure can use local system information to generate -- package.buildinfo and possibly other files. -- | Deprecated: Use simpleUserHooks or autoconfUserHooks, unless you -- need Cabal-1.2 compatibility in which case you must stick with -- defaultUserHooks defaultUserHooks :: UserHooks -- | Empty UserHooks which do nothing. emptyUserHooks :: UserHooks -- | Optional auxiliary package information file -- (pkgname.buildinfo) defaultHookedPackageDesc :: IO (Maybe FilePath)