Compiler versions

David Roundy droundy at abridgegame.org
Wed Apr 7 07:19:20 EDT 2004


On Wed, Apr 07, 2004 at 10:59:45AM +0100, Simon Peyton-Jones wrote:
> Library folk
> 
> Below is a suggestion from George that initially appears to be about
> Template Haskell: access to the GHC version identity.  But of course
> it's not strictly a TH thing: we could simply provide a module
> 
> 	module GHC.Version where
> 	   ghcVersion :: Int
> 
> and then you could import that module anywhere, including in your TH
> program:
> 
> 	import GHC.Version
> 	$( if ghcVersion > ... then ... )
> 
> And indeed such a thing might be more generally useful, across all
> Haskell implementations not just GHC.  Perhaps it should be
> 
>      module System.Compiler where
> 	compilerName :: String
> 	releaseDate :: CalendarTime 	-- or (Day,Month,Year)?
> 	version :: (Int,Int)
> 	patchLevel :: Int

With the scheme of a triple of Ints, you could have problems with versions
like 6.2.1pre1 or 6.2.1rc1 which can't easily be mapped to a triple of
Ints.

I prefer George's idea of an abstract version type which is an instance of
Show, Read and Ord.  I'd probably also add majorVersion and minorVersion
functions, which could return perhaps the same abstract type.  This could
also be extended to allow the versions of CVS checkouts to be dealt
with--they could have version numbers like 6.2.1cvs20040402 or something.
Most importantly, though, you wouldn't be defining a version numbering
policy in the interface.

(Internally I have nothing against a triple of Ints or even a single Int to
store the versions, I just don't like the idea of forcing all haskell
compilers ever--that support this interface--to use the same version
numbering scheme.)
-- 
David Roundy
http://www.abridgegame.org


More information about the Libraries mailing list