Get rid of Build.Info file, move compiler version to Elm.Internal.Version and use Elm's version conventions

This commit is contained in:
Evan Czaplicki 2013-12-17 11:36:05 -08:00
parent b9056797ec
commit 26a8c82b6f
8 changed files with 24 additions and 34 deletions

View file

@ -85,7 +85,6 @@ Library
Build.Dependencies,
Build.File,
Build.Flags,
Build.Info,
Build.Print,
Build.Source,
Build.Utils,
@ -165,7 +164,6 @@ Executable elm
Build.Dependencies,
Build.File,
Build.Flags,
Build.Info,
Build.Print,
Build.Source,
Build.Utils,

View file

@ -1,7 +1,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
module Build.Flags where
import qualified Build.Info as Info
import qualified Elm.Internal.Version as Version
import System.Console.CmdArgs
data Flags = Flags
@ -40,5 +40,5 @@ flags = Flags
&= help "Print out infered types of top-level definitions."
} &= help "Compile Elm programs to HTML, CSS, and JavaScript."
&= helpArg [explicit, name "help", name "h"]
&= versionArg [explicit, name "version", name "v", summary Info.version]
&= summary ("The Elm Compiler " ++ Info.version ++ ", (c) Evan Czaplicki 2011-2013")
&= versionArg [explicit, name "version", name "v", summary (show Version.elmVersion)]
&= summary ("The Elm Compiler " ++ show Version.elmVersion ++ ", (c) Evan Czaplicki 2011-2013")

View file

@ -1,11 +0,0 @@
module Build.Info where
import qualified Paths_Elm as This
import qualified Data.Version as Version
version :: String
version = Version.showVersion This.version
runtime :: IO FilePath
runtime = This.getDataFileName "elm-runtime.js"

View file

@ -2,6 +2,7 @@ module Main where
import Control.Monad (foldM)
import qualified Data.Map as Map
import qualified Data.Maybe as Maybe
import qualified Text.Blaze.Html.Renderer.Utf8 as Blaze
import qualified Data.ByteString.Lazy.Char8 as BS
import qualified System.Console.CmdArgs as CmdArgs
@ -13,9 +14,9 @@ import Build.Dependencies (getSortedDependencies)
import qualified Generate.Html as Html
import qualified Metadata.Prelude as Prelude
import qualified Build.Utils as Utils
import qualified Build.Info as Info
import qualified Build.Flags as Flag
import qualified Build.File as File
import qualified Elm.Internal.Paths as Path
main :: IO ()
main = do setNumCapabilities =<< getNumProcessors
@ -46,7 +47,7 @@ build flags rootFile =
then do putStr "Generating JavaScript ... "
return ("js", js)
else do putStr "Generating HTML ... "
makeHtml js moduleName
return (makeHtml js moduleName)
let targetFile = Utils.buildPath flags rootFile extension
createDirectoryIfMissing True (takeDirectory targetFile)
@ -61,11 +62,7 @@ build flags rootFile =
sources js = map Html.Link (Flag.scripts flags) ++ [ Html.Source js ]
makeHtml js moduleName = do
rtsPath <- case Flag.runtime flags of
Just fp -> return fp
Nothing -> Info.runtime
let html = Html.generate
rtsPath (takeBaseName rootFile) (sources js) moduleName ""
return ("html", Blaze.renderHtml html)
makeHtml js moduleName = ("html", Blaze.renderHtml html)
where
rtsPath = Maybe.fromMaybe Path.runtime (Flag.runtime flags)
html = Html.generate rtsPath (takeBaseName rootFile) (sources js) moduleName ""

View file

@ -25,4 +25,4 @@ interfaces = unsafePerformIO $ Prelude.interfaces
-- |This function extracts the module name of a given source program.
moduleName :: String -> Maybe String
moduleName = Parser.getModuleName
moduleName = Parser.getModuleName

View file

@ -8,6 +8,12 @@ import Data.Char (isDigit)
import qualified Data.List as List
import Data.Typeable
import qualified Data.Text as T
import qualified Paths_Elm as This
import qualified Data.Version as Version
elmVersion :: Version
elmVersion = V ns ""
where (Version.Version ns _) =This.version
-- Data representation

View file

@ -6,8 +6,7 @@ module InterfaceSerialization ( loadInterface
import qualified Data.ByteString.Lazy as L
import qualified Data.Binary as Binary
import Paths_Elm (version)
import Data.Version (showVersion)
import qualified Elm.Internal.Version as Version
import System.Directory (doesFileExist)
import System.IO (hPutStrLn, stderr)
import System.Exit (exitFailure)
@ -42,11 +41,12 @@ interfaceDecode filePath bytes = do
validVersion :: FilePath -> (String, ModuleInterface) ->
Either String (String, ModuleInterface)
validVersion filePath (name, interface) =
if iVersion interface == showVersion version then
if iVersion interface == Version.elmVersion then
Right (name, interface)
else
Left $ concat
[ "Error reading build artifact: ", filePath, "\n"
, " It was generated by a different version of the compiler: ", iVersion interface, "\n"
, " It was generated by a different version of the compiler: "
, show (iVersion interface), "\n"
, " Please remove the file and try again.\n"
]

View file

@ -14,7 +14,7 @@ import SourceSyntax.Type
import System.FilePath (joinPath)
import Control.Monad (liftM)
import qualified Build.Info as Info
import qualified Elm.Internal.Version as Version
data Module tipe var =
Module [String] Exports Imports [Declaration tipe var]
@ -61,7 +61,7 @@ type Interfaces = Map.Map String ModuleInterface
type ADT = (String, [String], [(String,[Type])])
data ModuleInterface = ModuleInterface {
iVersion :: String,
iVersion :: Version.Version,
iTypes :: Map.Map String Type,
iImports :: [(String, ImportMethod)],
iAdts :: [ADT],
@ -71,7 +71,7 @@ data ModuleInterface = ModuleInterface {
metaToInterface metaModule =
ModuleInterface
{ iVersion = Info.version
{ iVersion = Version.elmVersion
, iTypes = types metaModule
, iImports = imports metaModule
, iAdts = datatypes metaModule