
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 So then a program could ask whether it was being run by Hugs or GHC or whatever. Questions: * Would this be a good thing to agree across compilers? * What should the interface be? I gave one possibility above; George gives another. * I imagine this'd be useful for the library infrastructure project, somehow. Would anyone like to run with this to get an interface agreed? From the GHC end we'd be happy to implement any agreed interface. Simon -----Original Message----- From: George Russell [mailto:ger@informatik.uni-bremen.de] Sent: 07 April 2004 10:46 To: Simon Peyton-Jones Subject: Re: mkName and qualified names George Russell wrote:
incidentally you asked for priorities. Mine are (still)
Oh, and another one, (3) access to the current GHC version. For example data GhcVersion instance Read GhcVersion instance Ord GhcVersion thisVersion :: GhcVersion then you can do $( if thisVersion >= read "6.4.1" then [dd| -- use whizzo new features ... |] else [dd| -- sigh. painful workaround for Luddites ... |] ) This isn't nearly as important to me as the other two suggestions I made, however I presume it would be easier to implement. best wishes and thanks, George

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

"Simon Peyton-Jones"
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
So then a program could ask whether it was being run by Hugs or GHC or whatever.
I remember Mark Jones suggesting more-or-less exactly this idea back in about 1998/1999. It has been implemented in nhc98 ever since, but I finally deleted it from CVS recently because no other systems supported it. And (probably the more major reason) because I frequently forgot to keep it up to date. Here was the signature: module Haskell where import Time import Locale systemName :: String -- "Hugs", "GHC", "hbc", "nhc", "qhc", ... haskellVersion :: Int -- 13, 14, 98, 2000, ... releaseDate :: CalendarTime -- ... version :: String -- some combination of the above
Questions: * Would this be a good thing to agree across compilers?
Yes.
* What should the interface be? I gave one possibility above; George gives another.
I'm agnostic. Regards, Malcolm

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.

FWIW, I think that the LIP can indeed use such a thing. A library can
indicate what versions of a compiler it is dependent upon, and check
that in a test suite, for instance. I can't think of a lot of other
uses offhand...
George Russell
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.
The library infrastructure project already implements a basic Distribution.Version type (which I hope will become a standard). It only has dates and basic numeric versioning, along with a variety of ways to parse dates. (I had suggested a while ago that someone should help me implement more complex versions and version string parsing; that's a non-critical-path job that I can easily delegate.) Debian has some kind of rules for this that might be good to base the implementation on. Here's what we have right now: data Version = DateVersion {versionYear :: Integer, versionMonth :: Month, versionDay :: Integer} | NumberedVersion {versionMajor :: Integer, versionMinor :: Integer, versionPatchLevel :: Integer} | NoVersion deriving (Read, Show, Eq, Ord) I like the tags idea a lot. I don't know if your "version" function will work for something like hugs with date-based versions, though it's probably better than my NumberedVersion. I was thinking we'd have a handful of other pre-set versions, along with ways to compare them, and maybe a catchall "OtherVersion String" type. It should definitely implement Ord and Eq, but what should we do if someone tries to compare a DateVersion with a NumberedVersion, for instance? This could possibly happen if a project changed their versioning scheme. Maybe Version should be a typeclass where we provide a handful of defaults like DateVersion and NumberedVersion, and each type will have to provide a 'canonicalize' function much like your "version" function (actually, maybe Ord is good enough)? peace, isaac

"Simon Peyton-Jones"
Would anyone like to run with this to get an interface agreed? From the GHC end we'd be happy to implement any agreed interface. (snip)
To bring this around a little, I think I had proposed somewhere along the line that each library (and even Main modules perhaps) export a "toolInfo" variable which is based on Distribution.Package.PackageConfig type (which itself is based on types used in ghc-pkg). So I'm a little less sure at this point exactly which datatype should be exported, but it should have at least some of the fields in PackageConfig (which is below for your reference). I think it would be nice for most tools to export something along the lines of: ToolInfo PkgIdentifier {- includes version and name -} License String -- copyright String -- maintainer String -- stability But let's make sure I have the various configuration data types down first. Hopefully that'll happen Real Soon Now :) peace, isaac data PackageConfig = Package { pkgIdent :: PkgIdentifier, license :: License, copyright :: String, maintainer :: String, stability :: String, auto :: Bool, importDirs :: [FilePath], sourceDirs :: [FilePath], libraryDirs :: [FilePath], hsLibraries :: [String], extraLibraries :: [String], includeDirs :: [FilePath], cIncludes :: [String], depends :: [Dependency], -- use dependencies extraHugsOpts :: [Opt], extraCcOpts :: [Opt], extraLdOpts :: [Opt], frameworkDirs :: [FilePath], extraFrameworks:: [String]} deriving (Read, Show) data PkgIdentifier = PkgIdentifier {pkgName::String, pkgVersion::Version} data License = GPL | LGPL | BSD3 | BSD4 | PublicDomain | AllRightsReserved | {- ... | -} OtherLicense FilePath deriving (Read, Show) data SourcePackage = SourcePackage { pkgIdent :: PkgIdentifier, depends :: [Dependency], setupScript :: Either FilePath (String, FilePath) } deriving (Show, Read)
participants (5)
-
David Roundy
-
George Russell
-
Isaac Jones
-
Malcolm Wallace
-
Simon Peyton-Jones