Compiler versions
George Russell
ger at informatik.uni-bremen.de
Wed Apr 7 14:15:06 EDT 2004
Simon Peyton-Jones wrote (snipped):
> 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
This looks better than my interface, since you could do
if version >= (6,2)
or indeed
if (version,patchLevel) == ((6,2),1)
allowing you to select what exactly you match on.
But I would suggest instead providing an abstract type Version.
This would allow
(a) users to define Version's for their own software;
(b) compilers to have several Version's. For example, with GHC it seems
very plausible that you would have one version for the RTS, another for
the library shared with Hugs and NHC; and perhaps yet another for any
other major library component which goes through a series of major
incompatible changes (as used to be the case with the FFI).
Then a minimal interface for deconstructing Versions might be:
data Version
-- abstract
name :: Version -> String
-- "GHC", "Hugs", "FFI" for example.
version :: Version -> [Int]
-- major version would be 0th element, and so on.
-- Then I can do (if version compilerVersion >= [6,2,1]) or
-- (if take 2 (version compilerVersion) == [6,2])
timestamp :: ClockTime
-- better than CalendarTime in my opinion.
and perhaps
tags :: Version -> [String]
-- miscellaneous other unspecified qualifiers, for example
-- "hacked-for-windows", "experimental" and so on.
More information about the Libraries
mailing list