Skip to content
GitLab
Menu
Projects
Groups
Snippets
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
Packages
Cabal
Commits
7e759751
Commit
7e759751
authored
Aug 29, 2014
by
ttuegel
Browse files
Add instance Binary LocalBuildInfo
parent
ba27d815
Changes
18
Hide whitespace changes
Inline
Side-by-side
Cabal/Cabal.cabal
View file @
7e759751
...
...
@@ -128,6 +128,7 @@ source-repository head
library
build-depends:
base >= 4.2 && < 5,
binary >= 0.7 && < 0.8,
deepseq >= 1.3 && < 1.4,
filepath >= 1 && < 1.4,
directory >= 1 && < 1.3,
...
...
@@ -138,6 +139,10 @@ library
pretty >= 1 && < 1.2,
bytestring >= 0.9
-- Needed for GHC.Generics before GHC 7.6
if impl(ghc < 7.6)
build-depends: ghc-prim >= 0.2 && < 0.3
if !os(windows)
build-depends:
unix >= 2.0 && < 2.8
...
...
Cabal/Distribution/Compiler.hs
View file @
7e759751
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Compiler
...
...
@@ -35,10 +37,12 @@ module Distribution.Compiler (
CompilerId
(
..
),
)
where
import
Data.Binary
(
Binary
)
import
Data.Data
(
Data
)
import
Data.Typeable
(
Typeable
)
import
Data.Maybe
(
fromMaybe
)
import
Distribution.Version
(
Version
(
..
))
import
GHC.Generics
(
Generic
)
import
qualified
System.Info
(
compilerName
,
compilerVersion
)
import
Distribution.Text
(
Text
(
..
),
display
)
...
...
@@ -52,7 +56,9 @@ import Control.Monad (when)
data
CompilerFlavor
=
GHC
|
NHC
|
YHC
|
Hugs
|
HBC
|
Helium
|
JHC
|
LHC
|
UHC
|
HaskellSuite
String
-- string is the id of the actual compiler
|
OtherCompiler
String
deriving
(
Show
,
Read
,
Eq
,
Ord
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Read
,
Eq
,
Ord
,
Typeable
,
Data
)
instance
Binary
CompilerFlavor
knownCompilerFlavors
::
[
CompilerFlavor
]
knownCompilerFlavors
=
[
GHC
,
NHC
,
YHC
,
Hugs
,
HBC
,
Helium
,
JHC
,
LHC
,
UHC
]
...
...
@@ -125,7 +131,9 @@ defaultCompilerFlavor = case buildCompilerFlavor of
-- ------------------------------------------------------------
data
CompilerId
=
CompilerId
CompilerFlavor
Version
deriving
(
Eq
,
Ord
,
Read
,
Show
)
deriving
(
Eq
,
Generic
,
Ord
,
Read
,
Show
)
instance
Binary
CompilerId
instance
Text
CompilerId
where
disp
(
CompilerId
f
(
Version
[]
_
))
=
disp
f
...
...
Cabal/Distribution/InstalledPackageInfo.hs
View file @
7e759751
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.InstalledPackageInfo
...
...
@@ -89,6 +91,9 @@ import Distribution.Text
import
Text.PrettyPrint
as
Disp
import
qualified
Distribution.Compat.ReadP
as
Parse
import
Data.Binary
(
Binary
)
import
GHC.Generics
(
Generic
)
-- -----------------------------------------------------------------------------
-- The InstalledPackageInfo type
...
...
@@ -131,7 +136,9 @@ data InstalledPackageInfo_ m
haddockInterfaces
::
[
FilePath
],
haddockHTMLs
::
[
FilePath
]
}
deriving
(
Read
,
Show
)
deriving
(
Generic
,
Read
,
Show
)
instance
Binary
m
=>
Binary
(
InstalledPackageInfo_
m
)
instance
Package
.
Package
(
InstalledPackageInfo_
str
)
where
packageId
=
sourcePackageId
...
...
@@ -192,7 +199,9 @@ data ModuleReexport = ModuleReexport {
moduleReexportDefiningName
::
ModuleName
,
moduleReexportName
::
ModuleName
}
deriving
(
Read
,
Show
)
deriving
(
Generic
,
Read
,
Show
)
instance
Binary
ModuleReexport
instance
Text
ModuleReexport
where
disp
(
ModuleReexport
pkgid
origname
newname
)
=
...
...
Cabal/Distribution/License.hs
View file @
7e759751
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.License
...
...
@@ -51,9 +53,11 @@ import Distribution.Text (Text(..), display)
import
qualified
Distribution.Compat.ReadP
as
Parse
import
qualified
Text.PrettyPrint
as
Disp
import
Text.PrettyPrint
((
<>
))
import
Data.Binary
(
Binary
)
import
qualified
Data.Char
as
Char
(
isAlphaNum
)
import
Data.Data
(
Data
)
import
Data.Typeable
(
Typeable
)
import
GHC.Generics
(
Generic
)
-- | 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
...
...
@@ -110,7 +114,9 @@ data License =
-- | Indicates an erroneous license name.
|
UnknownLicense
String
deriving
(
Read
,
Show
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Read
,
Show
,
Eq
,
Typeable
,
Data
)
instance
Binary
License
-- | The list of all currently recognised licenses.
knownLicenses
::
[
License
]
...
...
Cabal/Distribution/ModuleName.hs
View file @
7e759751
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.ModuleName
...
...
@@ -22,21 +24,25 @@ module Distribution.ModuleName (
import
Distribution.Text
(
Text
(
..
)
)
import
Data.Binary
(
Binary
)
import
qualified
Data.Char
as
Char
(
isAlphaNum
,
isUpper
)
import
Data.Data
(
Data
)
import
Data.Typeable
(
Typeable
)
import
qualified
Distribution.Compat.ReadP
as
Parse
import
qualified
Text.PrettyPrint
as
Disp
import
qualified
Data.Char
as
Char
(
isAlphaNum
,
isUpper
)
import
System.FilePath
(
pathSeparator
)
import
Data.List
(
intercalate
,
intersperse
)
import
GHC.Generics
(
Generic
)
import
System.FilePath
(
pathSeparator
)
-- | A valid Haskell module name.
--
newtype
ModuleName
=
ModuleName
[
String
]
deriving
(
Eq
,
Ord
,
Read
,
Show
,
Typeable
,
Data
)
deriving
(
Eq
,
Generic
,
Ord
,
Read
,
Show
,
Typeable
,
Data
)
instance
Binary
ModuleName
instance
Text
ModuleName
where
disp
(
ModuleName
ms
)
=
...
...
Cabal/Distribution/Package.hs
View file @
7e759751
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Package
...
...
@@ -46,19 +48,24 @@ import Distribution.Text (Text(..))
import
qualified
Distribution.Compat.ReadP
as
Parse
import
Distribution.Compat.ReadP
((
<++
))
import
qualified
Text.PrettyPrint
as
Disp
import
Text.PrettyPrint
((
<>
),
(
<+>
),
text
)
import
Control.DeepSeq
(
NFData
(
..
))
import
Data.Binary
(
Binary
)
import
qualified
Data.Char
as
Char
(
isDigit
,
isAlphaNum
,
isUpper
,
isLower
,
ord
,
chr
)
import
Data.List
(
intercalate
,
sort
,
foldl'
)
import
Data.Data
(
Data
)
import
Data.List
(
intercalate
,
sort
,
foldl'
)
import
Data.Typeable
(
Typeable
)
import
GHC.Fingerprint
(
Fingerprint
(
..
),
fingerprintString
)
import
Data.Word
(
Word64
)
import
GHC.Fingerprint
(
Fingerprint
(
..
),
fingerprintString
)
import
GHC.Generics
(
Generic
)
import
Numeric
(
showIntAtBase
)
import
Text.PrettyPrint
((
<>
),
(
<+>
),
text
)
newtype
PackageName
=
PackageName
{
unPackageName
::
String
}
deriving
(
Read
,
Show
,
Eq
,
Ord
,
Typeable
,
Data
)
deriving
(
Generic
,
Read
,
Show
,
Eq
,
Ord
,
Typeable
,
Data
)
instance
Binary
PackageName
instance
Text
PackageName
where
disp
(
PackageName
n
)
=
Disp
.
text
n
...
...
@@ -84,7 +91,9 @@ data PackageIdentifier
pkgName
::
PackageName
,
-- ^The name of this package, eg. foo
pkgVersion
::
Version
-- ^the version of this package, eg 1.2
}
deriving
(
Read
,
Show
,
Eq
,
Ord
,
Typeable
,
Data
)
deriving
(
Generic
,
Read
,
Show
,
Eq
,
Ord
,
Typeable
,
Data
)
instance
Binary
PackageIdentifier
instance
Text
PackageIdentifier
where
disp
(
PackageIdentifier
n
v
)
=
case
v
of
...
...
@@ -108,7 +117,9 @@ instance NFData PackageIdentifier where
-- in a package database, or overlay of databases.
--
newtype
InstalledPackageId
=
InstalledPackageId
String
deriving
(
Read
,
Show
,
Eq
,
Ord
,
Typeable
,
Data
)
deriving
(
Generic
,
Read
,
Show
,
Eq
,
Ord
,
Typeable
,
Data
)
instance
Binary
InstalledPackageId
instance
Text
InstalledPackageId
where
disp
(
InstalledPackageId
str
)
=
text
str
...
...
@@ -137,7 +148,9 @@ data PackageKey
-- old versions of GHC assume that the 'sourcePackageId' recorded for an
-- installed package coincides with the package key it was compiled with.
|
OldPackageKey
!
PackageId
deriving
(
Read
,
Show
,
Eq
,
Ord
,
Typeable
,
Data
)
deriving
(
Generic
,
Read
,
Show
,
Eq
,
Ord
,
Typeable
,
Data
)
instance
Binary
PackageKey
-- | Convenience function which converts a fingerprint into a new-style package
-- key.
...
...
@@ -231,7 +244,9 @@ instance NFData PackageKey where
-- | Describes a dependency on a source package (API)
--
data
Dependency
=
Dependency
PackageName
VersionRange
deriving
(
Read
,
Show
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Read
,
Show
,
Eq
,
Typeable
,
Data
)
instance
Binary
Dependency
instance
Text
Dependency
where
disp
(
Dependency
name
ver
)
=
...
...
Cabal/Distribution/PackageDescription.hs
View file @
7e759751
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.PackageDescription
...
...
@@ -96,12 +98,14 @@ module Distribution.PackageDescription (
knownRepoTypes
,
)
where
import
Data.Binary
(
Binary
)
import
Data.Data
(
Data
)
import
Data.List
(
nub
,
intercalate
)
import
Data.Maybe
(
fromMaybe
,
maybeToList
)
import
Data.Monoid
(
Monoid
(
mempty
,
mappend
))
import
Data.Typeable
(
Typeable
)
import
Control.Monad
(
MonadPlus
(
mplus
))
import
GHC.Generics
(
Generic
)
import
Text.PrettyPrint
as
Disp
import
qualified
Distribution.Compat.ReadP
as
Parse
import
qualified
Data.Char
as
Char
(
isAlphaNum
,
isDigit
,
toLower
)
...
...
@@ -180,7 +184,9 @@ data PackageDescription
extraTmpFiles
::
[
FilePath
],
extraDocFiles
::
[
FilePath
]
}
deriving
(
Show
,
Read
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Read
,
Eq
,
Typeable
,
Data
)
instance
Binary
PackageDescription
instance
Package
PackageDescription
where
packageId
=
package
...
...
@@ -258,7 +264,9 @@ data BuildType
-- be built. Doing it this way rather than just giving a
-- parse error means we get better error messages and allows
-- you to inspect the rest of the package description.
deriving
(
Show
,
Read
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Read
,
Eq
,
Typeable
,
Data
)
instance
Binary
BuildType
knownBuildTypes
::
[
BuildType
]
knownBuildTypes
=
[
Simple
,
Configure
,
Make
,
Custom
]
...
...
@@ -285,7 +293,9 @@ data Library = Library {
libExposed
::
Bool
,
-- ^ Is the lib to be exposed by default?
libBuildInfo
::
BuildInfo
}
deriving
(
Show
,
Eq
,
Read
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Eq
,
Read
,
Typeable
,
Data
)
instance
Binary
Library
instance
Monoid
Library
where
mempty
=
Library
{
...
...
@@ -337,7 +347,9 @@ data ModuleReexport = ModuleReexport {
moduleReexportOriginalName
::
ModuleName
,
moduleReexportName
::
ModuleName
}
deriving
(
Eq
,
Read
,
Show
,
Typeable
,
Data
)
deriving
(
Eq
,
Generic
,
Read
,
Show
,
Typeable
,
Data
)
instance
Binary
ModuleReexport
instance
Text
ModuleReexport
where
disp
(
ModuleReexport
mpkgname
origname
newname
)
=
...
...
@@ -368,7 +380,9 @@ data Executable = Executable {
modulePath
::
FilePath
,
buildInfo
::
BuildInfo
}
deriving
(
Show
,
Read
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Read
,
Eq
,
Typeable
,
Data
)
instance
Binary
Executable
instance
Monoid
Executable
where
mempty
=
Executable
{
...
...
@@ -422,7 +436,9 @@ data TestSuite = TestSuite {
-- a better solution is waiting on the next overhaul to the
-- GenericPackageDescription -> PackageDescription resolution process.
}
deriving
(
Show
,
Read
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Read
,
Eq
,
Typeable
,
Data
)
instance
Binary
TestSuite
-- | The test suite interfaces that are currently defined. Each test suite must
-- specify which interface it supports.
...
...
@@ -448,7 +464,9 @@ data TestSuiteInterface =
-- the given reason (e.g. unknown test type).
--
|
TestSuiteUnsupported
TestType
deriving
(
Eq
,
Read
,
Show
,
Typeable
,
Data
)
deriving
(
Eq
,
Generic
,
Read
,
Show
,
Typeable
,
Data
)
instance
Binary
TestSuiteInterface
instance
Monoid
TestSuite
where
mempty
=
TestSuite
{
...
...
@@ -504,7 +522,9 @@ testModules test = (case testInterface test of
data
TestType
=
TestTypeExe
Version
-- ^ \"type: exitcode-stdio-x.y\"
|
TestTypeLib
Version
-- ^ \"type: detailed-x.y\"
|
TestTypeUnknown
String
Version
-- ^ Some unknown test type e.g. \"type: foo\"
deriving
(
Show
,
Read
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Read
,
Eq
,
Typeable
,
Data
)
instance
Binary
TestType
knownTestTypes
::
[
TestType
]
knownTestTypes
=
[
TestTypeExe
(
Version
[
1
,
0
]
[]
)
...
...
@@ -553,7 +573,9 @@ data Benchmark = Benchmark {
benchmarkEnabled
::
Bool
-- TODO: See TODO for 'testEnabled'.
}
deriving
(
Show
,
Read
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Read
,
Eq
,
Typeable
,
Data
)
instance
Binary
Benchmark
-- | The benchmark interfaces that are currently defined. Each
-- benchmark must specify which interface it supports.
...
...
@@ -575,7 +597,9 @@ data BenchmarkInterface =
-- interfaces for the given reason (e.g. unknown benchmark type).
--
|
BenchmarkUnsupported
BenchmarkType
deriving
(
Eq
,
Read
,
Show
,
Typeable
,
Data
)
deriving
(
Eq
,
Generic
,
Read
,
Show
,
Typeable
,
Data
)
instance
Binary
BenchmarkInterface
instance
Monoid
Benchmark
where
mempty
=
Benchmark
{
...
...
@@ -629,7 +653,9 @@ data BenchmarkType = BenchmarkTypeExe Version
-- ^ \"type: exitcode-stdio-x.y\"
|
BenchmarkTypeUnknown
String
Version
-- ^ Some unknown benchmark type e.g. \"type: foo\"
deriving
(
Show
,
Read
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Read
,
Eq
,
Typeable
,
Data
)
instance
Binary
BenchmarkType
knownBenchmarkTypes
::
[
BenchmarkType
]
knownBenchmarkTypes
=
[
BenchmarkTypeExe
(
Version
[
1
,
0
]
[]
)
]
...
...
@@ -683,7 +709,9 @@ data BuildInfo = BuildInfo {
-- simple assoc-list.
targetBuildDepends
::
[
Dependency
]
-- ^ Dependencies specific to a library or executable target
}
deriving
(
Show
,
Read
,
Eq
,
Typeable
,
Data
)
deriving
(
Generic
,
Show
,
Read
,
Eq
,
Typeable
,
Data
)
instance
Binary
BuildInfo
instance
Monoid
BuildInfo
where
mempty
=
BuildInfo
{
...
...
@@ -857,7 +885,9 @@ data SourceRepo = SourceRepo {
-- given the default is \".\" ie no subdirectory.
repoSubdir
::
Maybe
FilePath
}
deriving
(
Eq
,
Read
,
Show
,
Typeable
,
Data
)
deriving
(
Eq
,
Generic
,
Read
,
Show
,
Typeable
,
Data
)
instance
Binary
SourceRepo
-- | What this repo info is for, what it represents.
--
...
...
@@ -873,7 +903,9 @@ data RepoKind =
|
RepoThis
|
RepoKindUnknown
String
deriving
(
Eq
,
Ord
,
Read
,
Show
,
Typeable
,
Data
)
deriving
(
Eq
,
Generic
,
Ord
,
Read
,
Show
,
Typeable
,
Data
)
instance
Binary
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
...
...
@@ -882,7 +914,9 @@ data RepoKind =
data
RepoType
=
Darcs
|
Git
|
SVN
|
CVS
|
Mercurial
|
GnuArch
|
Bazaar
|
Monotone
|
OtherRepoType
String
deriving
(
Eq
,
Ord
,
Read
,
Show
,
Typeable
,
Data
)
deriving
(
Eq
,
Generic
,
Ord
,
Read
,
Show
,
Typeable
,
Data
)
instance
Binary
RepoType
knownRepoTypes
::
[
RepoType
]
knownRepoTypes
=
[
Darcs
,
Git
,
SVN
,
CVS
...
...
@@ -984,7 +1018,9 @@ data Flag = MkFlag
-- | A 'FlagName' is the name of a user-defined configuration flag
newtype
FlagName
=
FlagName
String
deriving
(
Eq
,
Ord
,
Show
,
Read
,
Typeable
,
Data
)
deriving
(
Eq
,
Generic
,
Ord
,
Show
,
Read
,
Typeable
,
Data
)
instance
Binary
FlagName
-- | A 'FlagAssignment' is a total or partial mapping of 'FlagName's to
-- 'Bool' flag values. It represents the flags chosen by the user or
...
...
Cabal/Distribution/Simple/Compiler.hs
View file @
7e759751
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.Compiler
...
...
@@ -52,9 +54,11 @@ import Distribution.Text (display)
import
Language.Haskell.Extension
(
Language
(
Haskell98
),
Extension
)
import
Control.Monad
(
liftM
)
import
Data.Binary
(
Binary
)
import
Data.List
(
nub
)
import
qualified
Data.Map
as
M
(
Map
,
lookup
)
import
Data.Maybe
(
catMaybes
,
isNothing
)
import
GHC.Generics
(
Generic
)
import
System.Directory
(
canonicalizePath
)
data
Compiler
=
Compiler
{
...
...
@@ -67,7 +71,9 @@ data Compiler = Compiler {
compilerProperties
::
M
.
Map
String
String
-- ^ A key-value map for properties not covered by the above fields.
}
deriving
(
Show
,
Read
)
deriving
(
Generic
,
Show
,
Read
)
instance
Binary
Compiler
showCompilerId
::
Compiler
->
String
showCompilerId
=
display
.
compilerId
...
...
@@ -92,7 +98,9 @@ compilerVersion = (\(CompilerId _ v) -> v) . compilerId
data
PackageDB
=
GlobalPackageDB
|
UserPackageDB
|
SpecificPackageDB
FilePath
deriving
(
Eq
,
Ord
,
Show
,
Read
)
deriving
(
Eq
,
Generic
,
Ord
,
Show
,
Read
)
instance
Binary
PackageDB
-- | We typically get packages from several databases, and stack them
-- together. This type lets us be explicit about that stacking. For example
...
...
@@ -142,7 +150,9 @@ absolutePackageDBPath (SpecificPackageDB db) =
data
OptimisationLevel
=
NoOptimisation
|
NormalOptimisation
|
MaximumOptimisation
deriving
(
Eq
,
Show
,
Read
,
Enum
,
Bounded
)
deriving
(
Bounded
,
Enum
,
Eq
,
Generic
,
Read
,
Show
)
instance
Binary
OptimisationLevel
flagToOptimisationLevel
::
Maybe
String
->
OptimisationLevel
flagToOptimisationLevel
Nothing
=
NormalOptimisation
...
...
Cabal/Distribution/Simple/InstallDirs.hs
View file @
7e759751
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.InstallDirs
...
...
@@ -41,9 +43,11 @@ module Distribution.Simple.InstallDirs (
)
where
import
Data.Binary
(
Binary
)
import
Data.List
(
isPrefixOf
)
import
Data.Maybe
(
fromMaybe
)
import
Data.Monoid
(
Monoid
(
..
))
import
GHC.Generics
(
Generic
)
import
System.Directory
(
getAppUserDataDirectory
)
import
System.FilePath
((
</>
),
isPathSeparator
,
pathSeparator
)
import
System.FilePath
(
dropDrive
)
...
...
@@ -89,7 +93,9 @@ data InstallDirs dir = InstallDirs {
htmldir
::
dir
,
haddockdir
::
dir
,
sysconfdir
::
dir
}
deriving
(
Read
,
Show
)
}
deriving
(
Generic
,
Read
,
Show
)
instance
Binary
dir
=>
Binary
(
InstallDirs
dir
)
instance
Functor
InstallDirs
where
fmap
f
dirs
=
InstallDirs
{
...
...
@@ -346,12 +352,16 @@ prefixRelativeInstallDirs pkgId pkg_key compilerId platform dirs =
-- | An abstract path, possibly containing variables that need to be
-- substituted for to get a real 'FilePath'.
--
newtype
PathTemplate
=
PathTemplate
[
PathComponent
]
newtype
PathTemplate
=
PathTemplate
[
PathComponent
]
deriving
(
Generic
)
instance
Binary
PathTemplate
data
PathComponent
=
Ordinary
FilePath
|
Variable
PathTemplateVariable
deriving
Eq
deriving
(
Eq
,
Generic
)
instance
Binary
PathComponent
data
PathTemplateVariable
=
PrefixVar
-- ^ The @$prefix@ path variable
...
...
@@ -374,7 +384,9 @@ data PathTemplateVariable =
|
TestSuiteResultVar
-- ^ The result of the test suite being run, eg
-- @pass@, @fail@, or @error@.
|
BenchmarkNameVar
-- ^ The name of the benchmark being run
deriving
Eq
deriving
(
Eq
,
Generic
)
instance
Binary
PathTemplateVariable
type
PathTemplateEnv
=
[(
PathTemplateVariable
,
PathTemplate
)]
...
...
Cabal/Distribution/Simple/LocalBuildInfo.hs
View file @
7e759751
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.LocalBuildInfo
...
...
@@ -78,11 +80,14 @@ import Distribution.Text
(
display
)
import
Distribution.System
(
Platform
)
import
Data.List
(
nub
,
find
)
import
Data.Graph
import
Data.Tree
(
flatten
)
import
Data.Array
((
!
))
import
Data.Binary
(
Binary
)
import
Data.Graph
import
Data.List
(
nub
,
find
)
import
Data.Maybe
import
Data.Tree
(
flatten
)
import
GHC.Generics
(
Generic
)
-- | Data cached after configuration step. See also
-- 'Distribution.Simple.Setup.ConfigFlags'.
...
...
@@ -134,7 +139,9 @@ data LocalBuildInfo = LocalBuildInfo {
stripLibs
::
Bool
,
-- ^Whether to strip libraries during install
progPrefix
::
PathTemplate
,
-- ^Prefix to be prepended to installed executables
progSuffix
::
PathTemplate
-- ^Suffix to be appended to installed executables
}
deriving
(
Read
,
Show
)
}
deriving
(
Generic
,
Read
,
Show
)
instance
Binary
LocalBuildInfo
-- | External package dependencies for the package as a whole. This is the
-- union of the individual 'componentPackageDeps', less any internal deps.
...
...
@@ -169,7 +176,9 @@ data ComponentName = CLibName -- currently only a single lib
|
CExeName
String
|
CTestName
String
|
CBenchName
String
deriving
(
Show
,
Eq
,
Ord
,
Read
)
deriving
(
Eq
,
Generic
,
Ord
,
Read
,
Show
)
instance
Binary
ComponentName
showComponentName
::
ComponentName
->
String
showComponentName
CLibName
=
"library"
...
...
@@ -196,7 +205,9 @@ data ComponentLocalBuildInfo
|
BenchComponentLocalBuildInfo
{
componentPackageDeps
::
[(
InstalledPackageId
,
PackageId
)]
}
deriving
(
Read
,
Show
)
deriving
(
Generic
,
Read
,
Show
)
instance
Binary
ComponentLocalBuildInfo
foldComponent
::
(
Library
->
a
)
->
(
Executable
->
a
)
...
...
@@ -210,7 +221,9 @@ foldComponent _ _ f _ (CTest tst) = f tst
foldComponent
_
_
_
f
(
CBench
bch
)
=
f
bch
data
LibraryName
=
LibraryName
String
deriving
(
Read
,
Show
)
deriving
(
Generic
,
Read
,
Show
)
instance
Binary
LibraryName
componentBuildInfo
::
Component
->
BuildInfo
componentBuildInfo
=
...
...
Cabal/Distribution/Simple/PackageIndex.hs
View file @
7e759751
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.PackageIndex
...
...
@@ -59,19 +61,21 @@ module Distribution.Simple.PackageIndex (
moduleNameIndex
,
)
where
import
Prelude
hiding
(
lookup
)
import
Control.Exception
(
assert
)
import
qualified
Data.Map
as
Map
import
Data.Map
(
Map
)
import
qualified
Data.Tree
as
Tree
import
qualified
Data.Graph
as
Graph
import
qualified
Data.Array
as
Array
import
Data.Array
((
!
))
import
qualified
Data.Array
as
Array