{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE CPP #-} module Main where import Control.Applicative (many, optional) #if !MIN_VERSION_base(4,11,0) import Data.Monoid ((<>)) #endif import qualified Data.Text as Text (unpack) import Data.Version (showVersion) import Options.Applicative ( Parser, execParser, fullDesc, info, header, help, helper, long, metavar , short, strArgument, strOption, value ) import Paths_SJW (version) import SJW (Source, compile, mainIs, source, sourceCode) data Config = Config { includes :: [String] , mainModuleName :: Maybe String , outputFile :: FilePath , target :: FilePath } deriving (Show) configParser :: Parser Config configParser = Config <$> many (strOption ( long "include" <> short 'I' <> metavar "PACKAGE" <> help "Include this package during compilation" )) <*> optional (strOption ( long "main-is" <> short 'm' <> metavar "MODULE_NAME" <> help "The name of the main module containing the code to run" )) <*> strOption ( long "output" <> short 'o' <> metavar "OUTPUT_PATH" <> help "The path where to create the compiled script (stdout if \"-\" or if the option is missing)" <> value "-" ) <*> strArgument ( metavar "SOURCE_DIR" <> help "The path where to look for the sources" ) getConfig :: IO Config getConfig = execParser $ info (helper <*> configParser) (fullDesc <> header ("SJW v" ++ showVersion version)) getSource :: Config -> Source getSource (Config {includes, mainModuleName = Nothing, target}) = source (target:includes) getSource (Config {includes, mainModuleName = Just moduleName, target}) = source (target:includes) `mainIs` moduleName main :: IO () main = do config@(Config {outputFile}) <- getConfig result <- SJW.sourceCode =<< SJW.compile (getSource config) case result of Nothing -> return () Just code -> output outputFile $ Text.unpack code where output "-" = putStr output fileName = writeFile fileName