add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / Data / Version.hs
index a57678f..7d7d329 100644 (file)
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP, DeriveDataTypeable #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Data.Version
@@ -6,7 +8,7 @@
 -- 
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  experimental
--- Portability :  portable
+-- Portability :  non-portable (local universal quantification in ReadP)
 --
 -- A general library for representation and manipulation of versions.
 -- 
 -----------------------------------------------------------------------------
 
 module Data.Version (
-       -- * The @Version@ type
-       Version(..),
-       -- * A concrete representation of @Version@
-       showVersion, parseVersion,
+        -- * The @Version@ type
+        Version(..),
+        -- * A concrete representation of @Version@
+        showVersion, parseVersion,
   ) where
 
+import Prelude -- necessary to get dependencies right
+
 -- These #ifdefs are necessary because this code might be compiled as
 -- part of ghc/lib/compat, and hence might be compiled by an older version
 -- of GHC.  In which case, we might need to pick up ReadP from 
 -- Distribution.Compat.ReadP, because the version in 
 -- Text.ParserCombinators.ReadP doesn't have all the combinators we need.
-#if __GLASGOW_HASKELL__ <= 602
-import Distribution.Compat.ReadP
-#else
+#if __GLASGOW_HASKELL__ || __HUGS__ || __NHC__
 import Text.ParserCombinators.ReadP
+#else
+import Distribution.Compat.ReadP
 #endif
 
-#if __GLASGOW_HASKELL__ < 602
-import Data.Dynamic    ( Typeable(..), TyCon, mkTyCon, mkAppTy )
+#if !__GLASGOW_HASKELL__
+import Data.Typeable    ( Typeable, TyCon, mkTyCon, mkTyConApp )
 #else
-import Data.Typeable   ( Typeable )
+import Data.Typeable    ( Typeable )
 #endif
 
-import Data.List       ( intersperse )
-import Control.Monad   ( liftM )
-import Data.Char       ( isDigit, isAlphaNum )
+import Data.List        ( intersperse, sort )
+import Control.Monad    ( liftM )
+import Data.Char        ( isDigit, isAlphaNum )
 
 {- |
 A 'Version' represents the version of a software entity.  
@@ -62,7 +66,7 @@ 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
+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.
@@ -76,42 +80,42 @@ representation may be more appropriate.
 -}
 data Version = 
   Version { versionBranch :: [Int],
-               -- ^ 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.
-
-          versionTags :: [String]  -- really a bag
-               -- ^ 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.
-       }
+                -- ^ 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.
+
+           versionTags :: [String]  -- really a bag
+                -- ^ 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.
+        }
   deriving (Read,Show
-#if __GLASGOW_HASKELL__ >= 602
-       ,Typeable
+#if __GLASGOW_HASKELL__
+        ,Typeable
 #endif
-       )
+        )
 
-#if __GLASGOW_HASKELL__ < 602
+#if !__GLASGOW_HASKELL__
 versionTc :: TyCon
-versionTc = mkTyCon "()"
+versionTc = mkTyCon "Version"
 
 instance Typeable Version where
-  typeOf _ = mkAppTy versionTc []
+  typeOf _ = mkTyConApp versionTc []
 #endif
 
 instance Eq Version where
   v1 == v2  =  versionBranch v1 == versionBranch v2 
-               && all (`elem` (versionTags v2)) (versionTags v1)
-               -- tags may be in any order
+                && sort (versionTags v1) == sort (versionTags v2)
+                -- tags may be in any order
 
 instance Ord Version where
   v1 `compare` v2 = versionBranch v1 `compare` versionBranch v2
@@ -121,7 +125,7 @@ instance Ord Version where
 
 -- | Provides one possible concrete representation for 'Version'.  For
 -- a version with 'versionBranch' @= [1,2,3]@ and 'versionTags' 
--- @= ["tag1","tag2"]@, the output will be @1.2.3-tag1-tag2@.
+-- @= [\"tag1\",\"tag2\"]@, the output will be @1.2.3-tag1-tag2@.
 --
 showVersion :: Version -> String
 showVersion (Version branch tags)
@@ -130,10 +134,12 @@ showVersion (Version branch tags)
 
 -- | A parser for versions in the format produced by 'showVersion'.
 --
-#if __GLASGOW_HASKELL__ <= 602
-parseVersion :: ReadP r Version
-#else
+#if __GLASGOW_HASKELL__ || __HUGS__
 parseVersion :: ReadP Version
+#elif __NHC__
+parseVersion :: ReadPN r Version
+#else
+parseVersion :: ReadP r Version
 #endif
 parseVersion = do branch <- sepBy1 (liftM read $ munch1 isDigit) (char '.')
                   tags   <- many (char '-' >> munch1 isAlphaNum)