module Language.Elm.Build (
Module,
Javascript,
BuildOptions(..),
ModuleName,
ModuleSource,
defaultOptions,
moduleFromString,
moduleFromFile,
buildModules,
buildModulesWithOptions
) where
import System.Process (readProcessWithExitCode)
import System.Directory (doesFileExist)
import System.Exit (ExitCode(..))
import Data.Maybe (catMaybes, fromMaybe)
import System.IO.Temp (withTempDirectory)
import Data.Text
import qualified Data.Text.IO as TextIO
type ModuleName = Text
type ModuleSource = Text
newtype InternalModule = Module (ModuleName, ModuleSource)
type Module = InternalModule
type Javascript = Text
data BuildOptions = BuildOptions {
elmBinPath :: Maybe String,
elmRuntimePath :: Maybe String,
makeHtml :: Bool
}
defaultOptions :: BuildOptions
defaultOptions = BuildOptions {
elmBinPath = Nothing,
elmRuntimePath = Nothing,
makeHtml = False
}
moduleFromString :: ModuleName -> ModuleSource -> Module
moduleFromString name source = Module (name, source)
moduleFromFile :: ModuleName -> FilePath -> IO Module
moduleFromFile name path = do
src <- TextIO.readFile path
return $ moduleFromString name src
buildModules :: Module -> [Module] -> IO (Either String Javascript)
buildModules = buildModulesWithOptions defaultOptions
buildModulesWithOptions :: BuildOptions -> Module -> [Module] -> IO (Either String Javascript)
buildModulesWithOptions options mainModule@(Module (mainName, _)) otherModules = withTempDirectory "" ".elm_temp" (\dir -> do
mapM_ (writeElmSource dir) otherModules
writeElmSource dir mainModule
let binPath = fromMaybe "elm" $ elmBinPath options
let runtimeOption = maybe Nothing (\path -> Just $ "--runtime=" ++ path) $ elmRuntimePath options
let genJSOption = if (makeHtml options) then Nothing else (Just "--only-js")
let resultExt = if (makeHtml options) then ".html" else ".js"
let cmdlineOptions = ["--make", "--build-dir=" ++ dir ++ "/build", "--cache-dir=" ++ dir ++"/cache", "--src-dir=" ++ dir] ++ catMaybes [runtimeOption, genJSOption] ++ [ unpack mainName ++ ".elm"]
(exitCode, stdout, stderr) <- readProcessWithExitCode binPath cmdlineOptions []
case exitCode of
ExitFailure i -> return $ Left $ "Elm failed with exit code " ++ (show i) ++ " and errors:" ++ stdout ++ stderr
_ -> do
let outputPath = dir ++ "/build/" ++ unpack mainName ++ resultExt
exists <- doesFileExist outputPath
case exists of
False -> return $ Left "Could not find output file from Elm"
_ -> do
retJS <- TextIO.readFile outputPath
return $ Right retJS
)
where
writeElmSource dir (Module (moduleName, source)) = do
let path = dir ++ "/" ++ unpack moduleName ++ ".elm"
TextIO.writeFile path source