ef9c07ddecbe778866d8f0ce2d827c79c895c920
[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 :  non-portable (local universal quantification in ReadP)
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 import Prelude -- necessary to get dependencies right
34
35 -- These #ifdefs are necessary because this code might be compiled as
36 -- part of ghc/lib/compat, and hence might be compiled by an older version
37 -- of GHC.  In which case, we might need to pick up ReadP from 
38 -- Distribution.Compat.ReadP, because the version in 
39 -- Text.ParserCombinators.ReadP doesn't have all the combinators we need.
40 #if __GLASGOW_HASKELL__ || __HUGS__ || __NHC__
41 import Text.ParserCombinators.ReadP
42 #else
43 import Distribution.Compat.ReadP
44 #endif
45
46 #if !__GLASGOW_HASKELL__
47 import Data.Typeable    ( Typeable, TyCon, mkTyCon, mkTyConApp )
48 #else
49 import Data.Typeable    ( Typeable )
50 #endif
51
52 import Data.List        ( intersperse, sort )
53 import Control.Monad    ( liftM )
54 import Data.Char        ( isDigit, isAlphaNum )
55
56 {- |
57 A 'Version' represents the version of a software entity.  
58
59 An instance of 'Eq' is provided, which implements exact equality
60 modulo reordering of the tags in the 'versionTags' field.
61
62 An instance of 'Ord' is also provided, which gives lexicographic
63 ordering on the 'versionBranch' fields (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2,
64 etc.).  This is expected to be sufficient for many uses, but note that
65 you may need to use a more specific ordering for your versioning
66 scheme.  For example, some versioning schemes may include pre-releases
67 which have tags @\"pre1\"@, @\"pre2\"@, and so on, and these would need to
68 be taken into account when determining ordering.  In some cases, date
69 ordering may be more appropriate, so the application would have to
70 look for @date@ tags in the 'versionTags' field and compare those.
71 The bottom line is, don't always assume that 'compare' and other 'Ord'
72 operations are the right thing for every 'Version'.
73
74 Similarly, concrete representations of versions may differ.  One
75 possible concrete representation is provided (see 'showVersion' and
76 'parseVersion'), but depending on the application a different concrete
77 representation may be more appropriate.
78 -}
79 data Version = 
80   Version { versionBranch :: [Int],
81                 -- ^ The numeric branch for this version.  This reflects the
82                 -- fact that most software versions are tree-structured; there
83                 -- is a main trunk which is tagged with versions at various
84                 -- points (1,2,3...), and the first branch off the trunk after
85                 -- version 3 is 3.1, the second branch off the trunk after
86                 -- version 3 is 3.2, and so on.  The tree can be branched
87                 -- arbitrarily, just by adding more digits.
88                 -- 
89                 -- We represent the branch as a list of 'Int', so
90                 -- version 3.2.1 becomes [3,2,1].  Lexicographic ordering
91                 -- (i.e. the default instance of 'Ord' for @[Int]@) gives
92                 -- the natural ordering of branches.
93
94            versionTags :: [String]  -- really a bag
95                 -- ^ A version can be tagged with an arbitrary list of strings.
96                 -- The interpretation of the list of tags is entirely dependent
97                 -- on the entity that this version applies to.
98         }
99   deriving (Read,Show
100 #if __GLASGOW_HASKELL__
101         ,Typeable
102 #endif
103         )
104
105 #if !__GLASGOW_HASKELL__
106 versionTc :: TyCon
107 versionTc = mkTyCon "Version"
108
109 instance Typeable Version where
110   typeOf _ = mkTyConApp versionTc []
111 #endif
112
113 instance Eq Version where
114   v1 == v2  =  versionBranch v1 == versionBranch v2 
115                 && sort (versionTags v1) == sort (versionTags v2)
116                 -- tags may be in any order
117
118 instance Ord Version where
119   v1 `compare` v2 = versionBranch v1 `compare` versionBranch v2
120
121 -- -----------------------------------------------------------------------------
122 -- A concrete representation of 'Version'
123
124 -- | Provides one possible concrete representation for 'Version'.  For
125 -- a version with 'versionBranch' @= [1,2,3]@ and 'versionTags' 
126 -- @= [\"tag1\",\"tag2\"]@, the output will be @1.2.3-tag1-tag2@.
127 --
128 showVersion :: Version -> String
129 showVersion (Version branch tags)
130   = concat (intersperse "." (map show branch)) ++ 
131      concatMap ('-':) tags
132
133 -- | A parser for versions in the format produced by 'showVersion'.
134 --
135 #if __GLASGOW_HASKELL__ || __HUGS__
136 parseVersion :: ReadP Version
137 #elif __NHC__
138 parseVersion :: ReadPN r Version
139 #else
140 parseVersion :: ReadP r Version
141 #endif
142 parseVersion = do branch <- sepBy1 (liftM read $ munch1 isDigit) (char '.')
143                   tags   <- many (char '-' >> munch1 isAlphaNum)
144                   return Version{versionBranch=branch, versionTags=tags}