[project @ 2004-11-11 17:48:49 by simonpj]
[ghc-base.git] / Data / Version.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.Version
4 -- Copyright   :  (c) The University of Glasgow 2004
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  portable
10 --
11 -- A general library for representation and manipulation of versions.
12 -- 
13 -- Versioning schemes are many and varied, so the version
14 -- representation provided by this library is intended to be a
15 -- compromise between complete generality, where almost no common
16 -- functionality could reasonably be provided, and fixing a particular
17 -- versioning scheme, which would probably be too restrictive.
18 -- 
19 -- So the approach taken here is to provide a representation which
20 -- subsumes many of the versioning schemes commonly in use, and we
21 -- provide implementations of 'Eq', 'Ord' and conversion to\/from 'String'
22 -- which will be appropriate for some applications, but not all.
23 --
24 -----------------------------------------------------------------------------
25
26 module Data.Version (
27         -- * The @Version@ type
28         Version(..),
29         -- * A concrete representation of @Version@
30         showVersion, parseVersion,
31   ) where
32
33 -- These #ifdefs are necessary because this code might be compiled as
34 -- part of ghc/lib/compat, and hence might be compiled by an older version
35 -- of GHC.  In which case, we might need to pick up ReadP from 
36 -- Distribution.Compat.ReadP, because the version in 
37 -- Text.ParserCombinators.ReadP doesn't have all the combinators we need.
38 #if __GLASGOW_HASKELL__ <= 602
39 import Distribution.Compat.ReadP
40 #else
41 import Text.ParserCombinators.ReadP
42 #endif
43
44 #if __GLASGOW_HASKELL__ < 602
45 import Data.Dynamic     ( Typeable(..), TyCon, mkTyCon, mkAppTy )
46 #else
47 import Data.Typeable    ( Typeable )
48 #endif
49
50 import Data.List        ( intersperse )
51 import Control.Monad    ( liftM )
52 import Data.Char        ( isDigit, isAlphaNum )
53
54 {- |
55 A 'Version' represents the version of a software entity.  
56
57 An instance of 'Eq' is provided, which implements exact equality
58 modulo reordering of the tags in the 'versionTags' field.
59
60 An instance of 'Ord' is also provided, which gives lexicographic
61 ordering on the 'versionBranch' fields (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2,
62 etc.).  This is expected to be sufficient for many uses, but note that
63 you may need to use a more specific ordering for your versioning
64 scheme.  For example, some versioning schemes may include pre-releases
65 which have tags @"pre1"@, @"pre2"@, and so on, and these would need to
66 be taken into account when determining ordering.  In some cases, date
67 ordering may be more appropriate, so the application would have to
68 look for @date@ tags in the 'versionTags' field and compare those.
69 The bottom line is, don't always assume that 'compare' and other 'Ord'
70 operations are the right thing for every 'Version'.
71
72 Similarly, concrete representations of versions may differ.  One
73 possible concrete representation is provided (see 'showVersion' and
74 'parseVersion'), but depending on the application a different concrete
75 representation may be more appropriate.
76 -}
77 data Version = 
78   Version { versionBranch :: [Int],
79                 -- ^ The numeric branch for this version.  This reflects the
80                 -- fact that most software versions are tree-structured; there
81                 -- is a main trunk which is tagged with versions at various
82                 -- points (1,2,3...), and the first branch off the trunk after
83                 -- version 3 is 3.1, the second branch off the trunk after
84                 -- version 3 is 3.2, and so on.  The tree can be branched
85                 -- arbitrarily, just by adding more digits.
86                 -- 
87                 -- We represent the branch as a list of 'Int', so
88                 -- version 3.2.1 becomes [3,2,1].  Lexicographic ordering
89                 -- (i.e. the default instance of 'Ord' for @[Int]@) gives
90                 -- the natural ordering of branches.
91
92            versionTags :: [String]  -- really a bag
93                 -- ^ A version can be tagged with an arbitrary list of strings.
94                 -- The interpretation of the list of tags is entirely dependent
95                 -- on the entity that this version applies to.
96         }
97   deriving (Read,Show
98 #if __GLASGOW_HASKELL__ >= 602
99         ,Typeable
100 #endif
101         )
102
103 #if __GLASGOW_HASKELL__ < 602
104 versionTc :: TyCon
105 versionTc = mkTyCon "()"
106
107 instance Typeable Version where
108   typeOf _ = mkAppTy versionTc []
109 #endif
110
111 instance Eq Version where
112   v1 == v2  =  versionBranch v1 == versionBranch v2 
113                 && all (`elem` (versionTags v2)) (versionTags v1)
114                 -- tags may be in any order
115
116 instance Ord Version where
117   v1 `compare` v2 = versionBranch v1 `compare` versionBranch v2
118
119 -- -----------------------------------------------------------------------------
120 -- A concrete representation of 'Version'
121
122 -- | Provides one possible concrete representation for 'Version'.  For
123 -- a version with 'versionBranch' @= [1,2,3]@ and 'versionTags' 
124 -- @= ["tag1","tag2"]@, the output will be @1.2.3-tag1-tag2@.
125 --
126 showVersion :: Version -> String
127 showVersion (Version branch tags)
128   = concat (intersperse "." (map show branch)) ++ 
129      concatMap ('-':) tags
130
131 -- | A parser for versions in the format produced by 'showVersion'.
132 --
133 #if __GLASGOW_HASKELL__ <= 602
134 parseVersion :: ReadP r Version
135 #else
136 parseVersion :: ReadP Version
137 #endif
138 parseVersion = do branch <- sepBy1 (liftM read $ munch1 isDigit) (char '.')
139                   tags   <- many (char '-' >> munch1 isAlphaNum)
140                   return Version{versionBranch=branch, versionTags=tags}