[project @ 2004-11-09 15:48:34 by simonmar]
authorsimonmar <unknown>
Tue, 9 Nov 2004 15:48:34 +0000 (15:48 +0000)
committersimonmar <unknown>
Tue, 9 Nov 2004 15:48:34 +0000 (15:48 +0000)
Adding Cabal to GHC, stage 1:

  - Add Data.Version library as previously discussed on
    libraries@haskell.org.

  - import the Cabal library as a package under fptools/libraries,
    build & install it by default.

  - Instead of importing Cabal's version of ReadP, I added the extra
    combinators to Text.ParserCombinators.ReadP.  If anyone objects,
    please speak up.

I made various changes to Cabal along the way, which I'll try to fold
back into the main Cabal sources in due course.  The changes are
roughly these:

  - Generic Version stuff removed from Distribution.Version (now in
    Data.Version).

  - Some modules were rearranged.  Distribution.Misc was replaced by
    Distribution.License & Distribution.Extension.  Distribution.Package
    split into D.PackageDescription and D.Package.

  - modules under Compat.* renamed to Distribution.Compat.*.  Hopefully
    I've retained enough compatibility stuff so that this will still build
    under nhc98 & Hugs.

  - Some elaboration of InstalledPackageInfo, which was previously unused
    in Cabal.  I've updated the type definition with respect to changes
    in PackageDescription, and added a parser/pretty-printer for it.
    This is going to be used in the new ghc-pkg.

  - Fixed a bug or two that I found along the way.

The next stage will be to integrate GHC's idea of packages with
Cabal's.  That means ghc-pkg must grok InstalledPackageInfo, and we
must use all the new information (versions, exposed/unexposed modules etc.).

Data/Version.hs [new file with mode: 0644]
Text/ParserCombinators/ReadP.hs

diff --git a/Data/Version.hs b/Data/Version.hs
new file mode 100644 (file)
index 0000000..959baf7
--- /dev/null
@@ -0,0 +1,109 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Data.Version
+-- Copyright   :  (c) The University of Glasgow 2004
+-- License     :  BSD-style (see the file libraries/base/LICENSE)
+-- 
+-- Maintainer  :  libraries@haskell.org
+-- Stability   :  experimental
+-- Portability :  portable
+--
+-- A general library for representation and manipulation of versions.
+-- 
+-- Versioning schemes are many and varied, so the version
+-- representation provided by this library is intended to be a
+-- compromise between complete generality, where almost no common
+-- functionality could reasonably be provided, and fixing a particular
+-- versioning scheme, which would probably be too restrictive.
+-- 
+-- So the approach taken here is to provide a representation which
+-- subsumes many of the versioning schemes commonly in use, and we
+-- provide implementations of 'Eq', 'Ord' and conversion to\/from 'String'
+-- which will be appropriate for some applications, but not all.
+--
+-----------------------------------------------------------------------------
+
+module Data.Version (
+       -- * The @Version@ type
+       Version(..),
+       -- * A concrete representation of @Version@
+       showVersion, parseVersion,
+  ) where
+
+import Text.ParserCombinators.ReadP
+import Data.Typeable   ( Typeable )
+import Data.List       ( intersperse )
+import Control.Monad   ( liftM )
+import Data.Char       ( isDigit, isAlphaNum )
+
+{- |
+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 { 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.
+       }
+  deriving (Read,Show,Typeable)
+
+instance Eq Version where
+  v1 == v2  =  versionBranch v1 == versionBranch v2 
+               && all (`elem` (versionTags v2)) (versionTags v1)
+               -- tags may be in any order
+
+instance Ord Version where
+  v1 `compare` v2 = versionBranch v1 `compare` versionBranch v2
+
+-- -----------------------------------------------------------------------------
+-- A concrete representation of 'Version'
+
+-- | 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@.
+--
+showVersion :: Version -> String
+showVersion (Version branch tags)
+  = concat (intersperse "." (map show branch)) ++ 
+     concatMap ('-':) tags
+
+-- | A parser for versions in the format produced by 'showVersion'.
+--
+parseVersion :: ReadP Version
+parseVersion = do branch <- sepBy1 (liftM read $ munch1 isDigit) (char '.')
+                  tags   <- many (char '-' >> munch1 isAlphaNum)
+                  return Version{versionBranch=branch, versionTags=tags}
index 18f91c4..b22290d 100644 (file)
@@ -38,6 +38,23 @@ module Text.ParserCombinators.ReadP
   munch1,     -- :: (Char -> Bool) -> ReadP String
   skipSpaces, -- :: ReadP ()
   choice,     -- :: [ReadP a] -> ReadP a
+  count,      -- :: Int -> ReadP a -> ReadP [a]
+  between,    -- :: ReadP open -> ReadP close -> ReadP a -> ReadP a
+  option,     -- :: a -> ReadP a -> ReadP a
+  optional,   -- :: ReadP a -> ReadP ()
+  many,       -- :: ReadP a -> ReadP [a]
+  many1,      -- :: ReadP a -> ReadP [a]
+  skipMany,   -- :: ReadP a -> ReadP ()
+  skipMany1,  -- :: ReadP a -> ReadP ()
+  sepBy,      -- :: ReadP a -> ReadP sep -> ReadP [a]
+  sepBy1,     -- :: ReadP a -> ReadP sep -> ReadP [a]
+  endBy,      -- :: ReadP a -> ReadP sep -> ReadP [a]
+  endBy1,     -- :: ReadP a -> ReadP sep -> ReadP [a]
+  chainr,     -- :: ReadP a -> ReadP (a -> a -> a) -> a -> ReadP a
+  chainl,     -- :: ReadP a -> ReadP (a -> a -> a) -> a -> ReadP a
+  chainl1,    -- :: ReadP a -> ReadP (a -> a -> a) -> ReadP a
+  chainr1,    -- :: ReadP a -> ReadP (a -> a -> a) -> ReadP a
+  manyTill,   -- :: ReadP a -> ReadP end -> ReadP [a]
   
   -- * Running a parser
   ReadS,      -- :: *; = String -> [(a,String)]
@@ -49,11 +66,13 @@ module Text.ParserCombinators.ReadP
   )
  where
 
-import Control.Monad( MonadPlus(..) )
+import Control.Monad( MonadPlus(..), sequence, liftM2 )
+
 #ifdef __GLASGOW_HASKELL__
 #ifndef __HADDOCK__
 import {-# SOURCE #-} GHC.Unicode ( isSpace  )
 #endif
+import GHC.List ( replicate )
 import GHC.Base
 #else
 import Data.Char( isSpace )
@@ -277,6 +296,101 @@ skipSpaces =
   skip (c:s) | isSpace c = do get; skip s
   skip _                 = do return ()
 
+count :: Int -> ReadP a -> ReadP [a]
+-- ^ @count n p@ parses @n@ occurrences of @p@ in sequence. A list of
+--   results is returned.
+count n p = sequence (replicate n p)
+
+between :: ReadP open -> ReadP close -> ReadP a -> ReadP a
+-- ^ @between open close p@ parses @open@, followed by @p@ and finally
+--   @close@. Only the value of @p@ is returned.
+between open close p = do open
+                          x <- p
+                          close
+                          return x
+
+option :: a -> ReadP a -> ReadP a
+-- ^ @option x p@ will either parse @p@ or return @x@ without consuming
+--   any input.
+option x p = p +++ return x
+
+optional :: ReadP a -> ReadP ()
+-- ^ @optional p@ optionally parses @p@ and always returns @()@.
+optional p = (p >> return ()) +++ return ()
+
+many :: ReadP a -> ReadP [a]
+-- ^ Parses zero or more occurrences of the given parser.
+many p = return [] +++ many1 p
+
+many1 :: ReadP a -> ReadP [a]
+-- ^ Parses one or more occurrences of the given parser.
+many1 p = liftM2 (:) p (many p)
+
+skipMany :: ReadP a -> ReadP ()
+-- ^ Like 'many', but discards the result.
+skipMany p = many p >> return ()
+
+skipMany1 :: ReadP a -> ReadP ()
+-- ^ Like 'many1', but discards the result.
+skipMany1 p = p >> skipMany p
+
+sepBy :: ReadP a -> ReadP sep -> ReadP [a]
+-- ^ @sepBy p sep@ parses zero or more occurrences of @p@, separated by @sep@.
+--   Returns a list of values returned by @p@.
+sepBy p sep = sepBy1 p sep +++ return []
+
+sepBy1 :: ReadP a -> ReadP sep -> ReadP [a]
+-- ^ @sepBy1 p sep@ parses one or more occurrences of @p@, separated by @sep@.
+--   Returns a list of values returned by @p@.
+sepBy1 p sep = liftM2 (:) p (many (sep >> p))
+
+endBy :: ReadP a -> ReadP sep -> ReadP [a]
+-- ^ @endBy p sep@ parses zero or more occurrences of @p@, separated and ended
+--   by @sep@.
+endBy p sep = many (do x <- p ; sep ; return x)
+
+endBy1 :: ReadP a -> ReadP sep -> ReadP [a]
+-- ^ @endBy p sep@ parses one or more occurrences of @p@, separated and ended
+--   by @sep@.
+endBy1 p sep = many1 (do x <- p ; sep ; return x)
+
+chainr :: ReadP a -> ReadP (a -> a -> a) -> a -> ReadP 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 p op x = chainr1 p op +++ return x
+
+chainl :: ReadP a -> ReadP (a -> a -> a) -> a -> ReadP 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 p op x = chainl1 p op +++ return x
+
+chainr1 :: ReadP a -> ReadP (a -> a -> a) -> ReadP a
+-- ^ Like 'chainr', but parses one or more occurrences of @p@.
+chainr1 p op = scan
+  where scan   = p >>= rest
+        rest x = do f <- op
+                    y <- scan
+                    return (f x y)
+                 +++ return x
+
+chainl1 :: ReadP a -> ReadP (a -> a -> a) -> ReadP a
+-- ^ Like 'chainl', but parses one or more occurrences of @p@.
+chainl1 p op = p >>= rest
+  where rest x = do f <- op
+                    y <- p
+                    rest (f x y)
+                 +++ return x
+
+manyTill :: ReadP a -> ReadP end -> ReadP [a]
+-- ^ @manyTill p end@ parses zero or more occurrences of @p@, until @end@
+--   succeeds. Returns a list of values returned by @p@.
+manyTill p end = scan
+  where scan = (end >> return []) <++ (liftM2 (:) p scan)
+
 -- ---------------------------------------------------------------------------
 -- Converting between ReadP and Read