Skip to content

Commit

Permalink
Add Data and Typeable instances for many types exported by Cabal.
Browse files Browse the repository at this point in the history
Note: this adds an orphan Data instance for Data.Version. A fix has been
proposed upstream.
  • Loading branch information
davidlazar committed Mar 18, 2013
1 parent 7597a17 commit 84ed9f2
Show file tree
Hide file tree
Showing 8 changed files with 56 additions and 35 deletions.
5 changes: 4 additions & 1 deletion Cabal/Distribution/Compiler.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Compiler
Expand Down Expand Up @@ -63,6 +64,8 @@ module Distribution.Compiler (
CompilerId(..),
) where

import Data.Data (Data)
import Data.Typeable (Typeable)
import Data.Maybe (fromMaybe)
import Distribution.Version (Version(..))

Expand All @@ -77,7 +80,7 @@ import Control.Monad (when)

data CompilerFlavor = GHC | NHC | YHC | Hugs | HBC | Helium | JHC | LHC | UHC
| OtherCompiler String
deriving (Show, Read, Eq, Ord)
deriving (Show, Read, Eq, Ord, Typeable, Data)

knownCompilerFlavors :: [CompilerFlavor]
knownCompilerFlavors = [GHC, NHC, YHC, Hugs, HBC, Helium, JHC, LHC, UHC]
Expand Down
5 changes: 4 additions & 1 deletion Cabal/Distribution/License.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.License
Expand Down Expand Up @@ -59,6 +60,8 @@ import qualified Distribution.Compat.ReadP as Parse
import qualified Text.PrettyPrint as Disp
import Text.PrettyPrint ((<>))
import qualified Data.Char as Char (isAlphaNum)
import Data.Data (Data)
import Data.Typeable (Typeable)

-- |This datatype indicates the license under which your package is
-- released. It is also wise to add your license to each source file
Expand Down Expand Up @@ -106,7 +109,7 @@ data License =
-- | Not a recognised license.
-- Allows us to deal with future extensions more gracefully.
| UnknownLicense String
deriving (Read, Show, Eq)
deriving (Read, Show, Eq, Typeable, Data)

knownLicenses :: [License]
knownLicenses = [ GPL unversioned, GPL (version [2]), GPL (version [3])
Expand Down
5 changes: 4 additions & 1 deletion Cabal/Distribution/ModuleName.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.ModuleName
Expand Down Expand Up @@ -50,6 +51,8 @@ module Distribution.ModuleName (
import Distribution.Text
( Text(..) )

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
Expand All @@ -62,7 +65,7 @@ import Data.List
-- | A valid Haskell module name.
--
newtype ModuleName = ModuleName [String]
deriving (Eq, Ord, Read, Show)
deriving (Eq, Ord, Read, Show, Typeable, Data)

instance Text ModuleName where
disp (ModuleName ms) =
Expand Down
9 changes: 5 additions & 4 deletions Cabal/Distribution/Package.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,10 +74,11 @@ import Text.PrettyPrint ((<>), (<+>), text)
import Control.DeepSeq (NFData(..))
import qualified Data.Char as Char ( isDigit, isAlphaNum )
import Data.List ( intercalate )
import Data.Data ( Data )
import Data.Typeable ( Typeable )

newtype PackageName = PackageName String
deriving (Read, Show, Eq, Ord, Typeable)
deriving (Read, Show, Eq, Ord, Typeable, Data)

instance Text PackageName where
disp (PackageName n) = Disp.text n
Expand All @@ -103,7 +104,7 @@ 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)
deriving (Read, Show, Eq, Ord, Typeable, Data)

instance Text PackageIdentifier where
disp (PackageIdentifier n v) = case v of
Expand All @@ -127,7 +128,7 @@ instance NFData PackageIdentifier where
-- in a package database, or overlay of databases.
--
newtype InstalledPackageId = InstalledPackageId String
deriving (Read,Show,Eq,Ord)
deriving (Read,Show,Eq,Ord,Typeable,Data)

instance Text InstalledPackageId where
disp (InstalledPackageId str) = text str
Expand All @@ -142,7 +143,7 @@ instance Text InstalledPackageId where
-- | Describes a dependency on a source package (API)
--
data Dependency = Dependency PackageName VersionRange
deriving (Read, Show, Eq)
deriving (Read, Show, Eq, Typeable, Data)

instance Text Dependency where
disp (Dependency name ver) =
Expand Down
41 changes: 21 additions & 20 deletions Cabal/Distribution/PackageDescription.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,7 @@ module Distribution.PackageDescription (
knownRepoTypes,
) where

import Data.Data (Data)
import Data.List (nub, intercalate)
import Data.Maybe (fromMaybe, maybeToList)
import Data.Monoid (Monoid(mempty, mappend))
Expand Down Expand Up @@ -196,7 +197,7 @@ data PackageDescription
extraTmpFiles :: [FilePath],
extraHtmlFiles :: [FilePath]
}
deriving (Show, Read, Eq)
deriving (Show, Read, Eq, Typeable, Data)

instance Package PackageDescription where
packageId = package
Expand Down Expand Up @@ -274,7 +275,7 @@ 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)
deriving (Show, Read, Eq, Typeable, Data)

knownBuildTypes :: [BuildType]
knownBuildTypes = [Simple, Configure, Make, Custom]
Expand All @@ -300,7 +301,7 @@ data Library = Library {
libExposed :: Bool, -- ^ Is the lib to be exposed by default?
libBuildInfo :: BuildInfo
}
deriving (Show, Eq, Read)
deriving (Show, Eq, Read, Typeable, Data)

instance Monoid Library where
mempty = Library {
Expand Down Expand Up @@ -348,7 +349,7 @@ data Executable = Executable {
modulePath :: FilePath,
buildInfo :: BuildInfo
}
deriving (Show, Read, Eq)
deriving (Show, Read, Eq, Typeable, Data)

instance Monoid Executable where
mempty = Executable {
Expand Down Expand Up @@ -402,7 +403,7 @@ data TestSuite = TestSuite {
-- a better solution is waiting on the next overhaul to the
-- GenericPackageDescription -> PackageDescription resolution process.
}
deriving (Show, Read, Eq)
deriving (Show, Read, Eq, Typeable, Data)

-- | The test suite interfaces that are currently defined. Each test suite must
-- specify which interface it supports.
Expand All @@ -428,7 +429,7 @@ data TestSuiteInterface =
-- the given reason (e.g. unknown test type).
--
| TestSuiteUnsupported TestType
deriving (Eq, Read, Show)
deriving (Eq, Read, Show, Typeable, Data)

instance Monoid TestSuite where
mempty = TestSuite {
Expand Down Expand Up @@ -484,7 +485,7 @@ 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)
deriving (Show, Read, Eq, Typeable, Data)

knownTestTypes :: [TestType]
knownTestTypes = [ TestTypeExe (Version [1,0] [])
Expand Down Expand Up @@ -533,7 +534,7 @@ data Benchmark = Benchmark {
benchmarkEnabled :: Bool
-- TODO: See TODO for 'testEnabled'.
}
deriving (Show, Read, Eq)
deriving (Show, Read, Eq, Typeable, Data)

-- | The benchmark interfaces that are currently defined. Each
-- benchmark must specify which interface it supports.
Expand All @@ -555,7 +556,7 @@ data BenchmarkInterface =
-- interfaces for the given reason (e.g. unknown benchmark type).
--
| BenchmarkUnsupported BenchmarkType
deriving (Eq, Read, Show)
deriving (Eq, Read, Show, Typeable, Data)

instance Monoid Benchmark where
mempty = Benchmark {
Expand Down Expand Up @@ -609,7 +610,7 @@ data BenchmarkType = BenchmarkTypeExe Version
-- ^ \"type: exitcode-stdio-x.y\"
| BenchmarkTypeUnknown String Version
-- ^ Some unknown benchmark type e.g. \"type: foo\"
deriving (Show, Read, Eq)
deriving (Show, Read, Eq, Typeable, Data)

knownBenchmarkTypes :: [BenchmarkType]
knownBenchmarkTypes = [ BenchmarkTypeExe (Version [1,0] []) ]
Expand Down Expand Up @@ -663,7 +664,7 @@ data BuildInfo = BuildInfo {
-- simple assoc-list.
targetBuildDepends :: [Dependency] -- ^ Dependencies specific to a library or executable target
}
deriving (Show,Read,Eq)
deriving (Show,Read,Eq,Typeable,Data)

instance Monoid BuildInfo where
mempty = BuildInfo {
Expand Down Expand Up @@ -837,7 +838,7 @@ data SourceRepo = SourceRepo {
-- given the default is \".\" ie no subdirectory.
repoSubdir :: Maybe FilePath
}
deriving (Eq, Read, Show)
deriving (Eq, Read, Show, Typeable, Data)

-- | What this repo info is for, what it represents.
--
Expand All @@ -853,7 +854,7 @@ data RepoKind =
| RepoThis

| RepoKindUnknown String
deriving (Eq, Ord, Read, Show)
deriving (Eq, Ord, Read, Show, Typeable, Data)

-- | 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
Expand All @@ -862,7 +863,7 @@ data RepoKind =
data RepoType = Darcs | Git | SVN | CVS
| Mercurial | GnuArch | Bazaar | Monotone
| OtherRepoType String
deriving (Eq, Ord, Read, Show)
deriving (Eq, Ord, Read, Show, Typeable, Data)

knownRepoTypes :: [RepoType]
knownRepoTypes = [Darcs, Git, SVN, CVS
Expand Down Expand Up @@ -945,7 +946,7 @@ data GenericPackageDescription =
condTestSuites :: [(String, CondTree ConfVar [Dependency] TestSuite)],
condBenchmarks :: [(String, CondTree ConfVar [Dependency] Benchmark)]
}
deriving (Show, Eq, Typeable)
deriving (Show, Eq, Typeable, Data)

instance Package GenericPackageDescription where
packageId = packageId . packageDescription
Expand All @@ -960,11 +961,11 @@ data Flag = MkFlag
, flagDefault :: Bool
, flagManual :: Bool
}
deriving (Show, Eq)
deriving (Show, Eq, Typeable, Data)

-- | A 'FlagName' is the name of a user-defined configuration flag
newtype FlagName = FlagName String
deriving (Eq, Ord, Show, Read)
deriving (Eq, Ord, Show, Read, Typeable, Data)

-- | A 'FlagAssignment' is a total or partial mapping of 'FlagName's to
-- 'Bool' flag values. It represents the flags chosen by the user or
Expand All @@ -978,7 +979,7 @@ data ConfVar = OS OS
| Arch Arch
| Flag FlagName
| Impl CompilerFlavor VersionRange
deriving (Eq, Show)
deriving (Eq, Show, Typeable, Data)

--instance Text ConfVar where
-- disp (OS os) = "os(" ++ display os ++ ")"
Expand All @@ -993,7 +994,7 @@ data Condition c = Var c
| CNot (Condition c)
| COr (Condition c) (Condition c)
| CAnd (Condition c) (Condition c)
deriving (Show, Eq)
deriving (Show, Eq, Typeable, Data)

--instance Text c => Text (Condition c) where
-- disp (Var x) = text (show x)
Expand All @@ -1009,7 +1010,7 @@ data CondTree v c a = CondNode
, CondTree v c a
, Maybe (CondTree v c a))]
}
deriving (Show, Eq)
deriving (Show, Eq, Typeable, Data)

--instance (Text v, Text c) => Text (CondTree v c a) where
-- disp (CondNode _dat cs ifs) =
Expand Down
9 changes: 6 additions & 3 deletions Cabal/Distribution/System.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.System
Expand Down Expand Up @@ -31,6 +32,8 @@ module Distribution.System (
import qualified System.Info (os, arch)
import qualified Data.Char as Char (toLower, isAlphaNum)

import Data.Data (Data)
import Data.Typeable (Typeable)
import Data.Maybe (fromMaybe, listToMaybe)
import Distribution.Text (Text(..), display)
import qualified Distribution.Compat.ReadP as Parse
Expand Down Expand Up @@ -66,7 +69,7 @@ data OS = Linux | Windows | OSX -- tier 1 desktop OSs
| HaLVM -- bare metal / VMs / hypervisors
| IOS -- iOS
| OtherOS String
deriving (Eq, Ord, Show, Read)
deriving (Eq, Ord, Show, Read, Typeable, Data)

--TODO: decide how to handle Android and iOS.
-- They are like Linux and OSX but with some differences.
Expand Down Expand Up @@ -116,7 +119,7 @@ data Arch = I386 | X86_64 | PPC | PPC64 | Sparc
| Alpha | Hppa | Rs6000
| M68k | Vax
| OtherArch String
deriving (Eq, Ord, Show, Read)
deriving (Eq, Ord, Show, Read, Typeable, Data)

knownArches :: [Arch]
knownArches = [I386, X86_64, PPC, PPC64, Sparc
Expand Down Expand Up @@ -157,7 +160,7 @@ buildArch = classifyArch Permissive System.Info.arch
-- ------------------------------------------------------------

data Platform = Platform Arch OS
deriving (Eq, Ord, Show, Read)
deriving (Eq, Ord, Show, Read, Typeable, Data)

instance Text Platform where
disp (Platform arch os) = disp arch <> Disp.char '-' <> disp os
Expand Down
8 changes: 6 additions & 2 deletions Cabal/Distribution/Version.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Version
Expand Down Expand Up @@ -92,6 +92,7 @@ module Distribution.Version (

) where

import Data.Data ( Data )
import Data.Typeable ( Typeable )
import Data.Version ( Version(..) )

Expand All @@ -118,7 +119,10 @@ data VersionRange
| UnionVersionRanges VersionRange VersionRange
| IntersectVersionRanges VersionRange VersionRange
| VersionRangeParens VersionRange -- just '(exp)' parentheses syntax
deriving (Show,Read,Eq,Typeable)
deriving (Show,Read,Eq,Typeable,Data)

-- TODO orphan
deriving instance Data Version

{-# DEPRECATED AnyVersion "Use 'anyVersion', 'foldVersionRange' or 'asVersionIntervals'" #-}
{-# DEPRECATED ThisVersion "use 'thisVersion', 'foldVersionRange' or 'asVersionIntervals'" #-}
Expand Down
Loading

0 comments on commit 84ed9f2

Please sign in to comment.