Skip to content

Commit

Permalink
Add some Typeable instances used by the Hackage 2 server
Browse files Browse the repository at this point in the history
  • Loading branch information
Ian Lynagh committed Aug 23, 2012
1 parent 43af8a4 commit 1a8fb83
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 4 deletions.
6 changes: 4 additions & 2 deletions Cabal/Distribution/Package.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Package
Expand Down Expand Up @@ -73,9 +74,10 @@ import Text.PrettyPrint ((<>), (<+>), text)
import Control.DeepSeq (NFData(..))
import qualified Data.Char as Char ( isDigit, isAlphaNum )
import Data.List ( intersperse )
import Data.Typeable ( Typeable )

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

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

instance Text PackageIdentifier where
disp (PackageIdentifier n v) = case v of
Expand Down
4 changes: 3 additions & 1 deletion Cabal/Distribution/PackageDescription.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.PackageDescription
Expand Down Expand Up @@ -126,6 +127,7 @@ module Distribution.PackageDescription (
import Data.List (nub, intersperse)
import Data.Maybe (maybeToList)
import Data.Monoid (Monoid(mempty, mappend))
import Data.Typeable ( Typeable )
import Control.Monad (MonadPlus(mplus))
import Text.PrettyPrint as Disp
import qualified Distribution.Compat.ReadP as Parse
Expand Down Expand Up @@ -952,7 +954,7 @@ data GenericPackageDescription =
condTestSuites :: [(String, CondTree ConfVar [Dependency] TestSuite)],
condBenchmarks :: [(String, CondTree ConfVar [Dependency] Benchmark)]
}
deriving (Show, Eq)
deriving (Show, Eq, Typeable)

instance Package GenericPackageDescription where
packageId = packageId . packageDescription
Expand Down
4 changes: 3 additions & 1 deletion Cabal/Distribution/Version.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Version
Expand Down Expand Up @@ -91,6 +92,7 @@ module Distribution.Version (

) where

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

import Distribution.Text ( Text(..) )
Expand All @@ -116,7 +118,7 @@ data VersionRange
| UnionVersionRanges VersionRange VersionRange
| IntersectVersionRanges VersionRange VersionRange
| VersionRangeParens VersionRange -- just '(exp)' parentheses syntax
deriving (Show,Read,Eq)
deriving (Show,Read,Eq,Typeable)

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

0 comments on commit 1a8fb83

Please sign in to comment.