{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} module Main (main) where import Data.Text (Text) import Data.Vector (Vector) import Options.Applicative as Opts import System.Directory (createDirectoryIfMissing) import System.FilePath ((), takeDirectory) import System.IO import qualified Data.Text as T import qualified Data.Text.IO as T import qualified Data.Vector as V import ProcessModule import ProcessRootModule #ifdef CABAL import Data.Version (showVersion) import qualified Paths_purescript_bundle_fast as Paths #endif programVersion :: String programVersion = #ifdef CABAL showVersion Paths.version #else "unknown-version (not built with cabal)" #endif -- | Command line options. data Options = Options { optionsInputDir :: FilePath , optionsOutputFile :: Maybe FilePath , optionsEntryPoints :: String , optionsMainModule :: Maybe String , optionsNamespace :: String } deriving Show app :: Options -> IO () app Options{..} = do case optionsOutputFile of Nothing -> process stdout Just filename -> do createDirectoryIfMissing True (takeDirectory filename) withFile filename WriteMode $ \h -> process h where process :: Handle -> IO () process outHandle = do T.hPutStrLn outHandle $ "// Generated by psc-bundle-fast " `T.append` T.pack programVersion T.hPutStrLn outHandle $ "var PS = { };" T.hPutStrLn outHandle $ "var require = function() { return function() { throw new Error('require is not supported in psc-bundle-fast'); }; };" processRootModule outHandle (T.pack optionsNamespace) (T.pack optionsEntryPoints) loadModule loadForeign case optionsMainModule of Nothing -> return () Just mainModule -> T.hPutStrLn outHandle (callMain (T.pack optionsNamespace) (T.pack mainModule)) loadModule :: ModuleName -> IO (Vector Text) loadModule moduleName = do contents <- T.readFile $ optionsInputDir T.unpack moduleName "index.js" return $ V.fromList (T.lines contents) loadForeign :: ModuleName -> IO Text loadForeign moduleName = T.readFile $ optionsInputDir T.unpack moduleName "foreign.js" callMain :: Namespace -> ModuleName -> Text callMain namespace modulename = T.concat [namespace, "[\"", modulename, "\"].main();"] -- | Command line options parser. options :: Parser Options options = Options <$> inputDir <*> optional outputFile <*> entryPoint <*> optional mainModule <*> namespace where inputDir :: Parser FilePath inputDir = strOption $ short 'i' <> metavar "DIR" <> long "input-dir" <> help "The directory containing the compiled modules. This directory should contain a subdirectory for each compiled module(with the name of the module), and within each of those there should be an index.js (and optional foreign.js) file. The psc compiler usually calls the desired directory \"output\"" outputFile :: Parser FilePath outputFile = strOption $ short 'o' <> metavar "FILE" <> long "output" <> help "The output .js file (Default is stdout)" entryPoint :: Parser String entryPoint = strOption $ short 'm' <> metavar "MODULE" <> long "module" <> help "Entry point module name(s). All code which is not a transitive dependency of an entry point module will be removed." mainModule :: Parser String mainModule = strOption $ long "main" <> metavar "MODULE" <> help "Generate code to run the main method in the specified module." namespace :: Parser String namespace = strOption $ short 'n' <> long "namespace" <> Opts.value "PS" <> showDefault <> help "Specify the namespace that PureScript modules will be exported to when running in the browser." -- | Make it go. main :: IO () main = do opts <- execParser (info (version <*> helper <*> options) infoModList) app opts where infoModList = fullDesc <> headerInfo <> footerInfo headerInfo = header "psc-bundle-fast - Bundles compiled PureScript modules for the browser (fast version, for development)" footerInfo = footer $ "psc-bundle-fast " ++ programVersion version :: Parser (a -> a) version = abortOption (InfoMsg programVersion) $ long "version" <> help "Show the version number" <> hidden