{-# LANGUAGE CPP #-} {-# LANGUAGE RecordWildCards #-} module Main (main) where import Control.Monad (unless) import Data.Monoid import Data.Version (showVersion) import Options.Applicative import System.Environment (getEnvironment) import System.Exit (ExitCode (ExitSuccess), exitWith, exitFailure) import System.Process (rawSystem) import AddHandler (addHandler) import Devel (DevelOpts (..), devel, develSignal) import Keter (keter) import Options (injectDefaults) import qualified Paths_yesod_bin import System.IO (hPutStrLn, stderr) import HsFile (mkHsFile) #ifndef WINDOWS import Build (touch) touch' :: IO () touch' = touch windowsWarning :: String windowsWarning = "" #else touch' :: IO () touch' = return () windowsWarning :: String windowsWarning = " (does not work on Windows)" #endif data CabalPgm = Cabal | CabalDev deriving (Show, Eq) data Options = Options { optCabalPgm :: CabalPgm , optVerbose :: Bool , optCommand :: Command } deriving (Show, Eq) data Command = Init [String] | HsFiles | Configure | Build { buildExtraArgs :: [String] } | Touch | Devel { develSuccessHook :: Maybe String , develExtraArgs :: [String] , develPort :: Int , develTlsPort :: Int , proxyTimeout :: Int , noReverseProxy :: Bool , develHost :: Maybe String } | DevelSignal | Test | AddHandler { addHandlerRoute :: Maybe String , addHandlerPattern :: Maybe String , addHandlerMethods :: [String] } | Keter { _keterNoRebuild :: Bool , _keterNoCopyTo :: Bool , _keterBuildArgs :: [String] } | Version deriving (Show, Eq) cabalCommand :: Options -> String cabalCommand mopt | optCabalPgm mopt == CabalDev = "cabal-dev" | otherwise = "cabal" main :: IO () main = do o <- execParser =<< injectDefaults "yesod" [ ("yesod.devel.extracabalarg" , \o args -> o { optCommand = case optCommand o of d@Devel{} -> d { develExtraArgs = args } c -> c }) , ("yesod.build.extracabalarg" , \o args -> o { optCommand = case optCommand o of b@Build{} -> b { buildExtraArgs = args } c -> c }) ] optParser' let cabal = rawSystem' (cabalCommand o) case optCommand o of Init _ -> initErrorMsg HsFiles -> mkHsFile Configure -> cabal ["configure"] Build es -> touch' >> cabal ("build":es) Touch -> touch' Keter{..} -> keter (cabalCommand o) _keterNoRebuild _keterNoCopyTo _keterBuildArgs Version -> putStrLn ("yesod-bin version: " ++ showVersion Paths_yesod_bin.version) AddHandler{..} -> addHandler addHandlerRoute addHandlerPattern addHandlerMethods Test -> cabalTest cabal Devel{..} -> devel DevelOpts { verbose = optVerbose o , successHook = develSuccessHook , develPort = develPort , develTlsPort = develTlsPort , proxyTimeout = proxyTimeout , useReverseProxy = not noReverseProxy , develHost = develHost } develExtraArgs DevelSignal -> develSignal where cabalTest cabal = do env <- getEnvironment case lookup "STACK_EXE" env of Nothing -> do touch' _ <- cabal ["configure", "--enable-tests", "-flibrary-only"] _ <- cabal ["build"] cabal ["test"] Just _ -> do hPutStrLn stderr "'yesod test' is no longer needed with Stack" hPutStrLn stderr "Instead, please just run 'stack test'" exitFailure initErrorMsg = do mapM_ putStrLn [ "The init command has been removed." , "Please use 'stack new