module Fay.Config
( Config
( configOptimize
, configFlattenApps
, configExportRuntime
, configExportStdlib
, configExportStdlibOnly
, configPrettyPrint
, configHtmlWrapper
, configSourceMap
, configHtmlJSLibs
, configLibrary
, configWarn
, configFilePath
, configTypecheck
, configWall
, configGClosure
, configPackageConf
, configBasePath
, configStrict
, configTypecheckOnly
, configRuntimePath
, configOptimizeNewtypes
, configPrettyThunks
, configPrettyOperators
, configShowGhcCalls
)
, defaultConfig
, defaultConfigWithSandbox
, configDirectoryIncludes
, configDirectoryIncludePaths
, nonPackageConfigDirectoryIncludePaths
, addConfigDirectoryInclude
, addConfigDirectoryIncludes
, addConfigDirectoryIncludePaths
, configPackages
, addConfigPackage
, addConfigPackages
, shouldExportStrictWrapper
) where
import Fay.Compiler.Prelude
import Data.Default
import Data.Maybe ()
import Language.Haskell.Exts (ModuleName (..))
import System.Environment
data Config = Config
{ configOptimize :: Bool
, configFlattenApps :: Bool
, configExportRuntime :: Bool
, configExportStdlib :: Bool
, configExportStdlibOnly :: Bool
, _configDirectoryIncludes :: [(Maybe String, FilePath)]
, configPrettyPrint :: Bool
, configHtmlWrapper :: Bool
, configSourceMap :: Bool
, configHtmlJSLibs :: [FilePath]
, configLibrary :: Bool
, configWarn :: Bool
, configFilePath :: Maybe FilePath
, configTypecheck :: Bool
, configWall :: Bool
, configGClosure :: Bool
, configPackageConf :: Maybe FilePath
, _configPackages :: [String]
, configBasePath :: Maybe FilePath
, configStrict :: [String]
, configTypecheckOnly :: Bool
, configRuntimePath :: Maybe FilePath
, configOptimizeNewtypes :: Bool
, configPrettyThunks :: Bool
, configPrettyOperators :: Bool
, configShowGhcCalls :: Bool
} deriving (Show)
defaultConfig :: Config
defaultConfig = addConfigPackage "fay-base"
Config
{ configOptimize = False
, configFlattenApps = False
, configExportRuntime = True
, configExportStdlib = True
, configExportStdlibOnly = False
, _configDirectoryIncludes = []
, configPrettyPrint = False
, configHtmlWrapper = False
, configHtmlJSLibs = []
, configLibrary = False
, configWarn = True
, configFilePath = Nothing
, configTypecheck = True
, configWall = False
, configGClosure = False
, configPackageConf = Nothing
, _configPackages = []
, configBasePath = Nothing
, configStrict = []
, configTypecheckOnly = False
, configRuntimePath = Nothing
, configSourceMap = False
, configOptimizeNewtypes = True
, configPrettyThunks = False
, configPrettyOperators = False
, configShowGhcCalls = False
}
defaultConfigWithSandbox :: IO Config
defaultConfigWithSandbox = do
packageConf <- fmap (lookup "HASKELL_PACKAGE_SANDBOX") getEnvironment
return defaultConfig { configPackageConf = packageConf }
instance Default Config where
def = defaultConfig
configDirectoryIncludes :: Config -> [(Maybe String, FilePath)]
configDirectoryIncludes = _configDirectoryIncludes
configDirectoryIncludePaths :: Config -> [FilePath]
configDirectoryIncludePaths = map snd . _configDirectoryIncludes
nonPackageConfigDirectoryIncludePaths :: Config -> [FilePath]
nonPackageConfigDirectoryIncludePaths = map snd . filter (isJust . fst) . _configDirectoryIncludes
addConfigDirectoryInclude :: Maybe String -> FilePath -> Config -> Config
addConfigDirectoryInclude pkg fp cfg = cfg { _configDirectoryIncludes = (pkg, fp) : _configDirectoryIncludes cfg }
addConfigDirectoryIncludes :: [(Maybe String,FilePath)] -> Config -> Config
addConfigDirectoryIncludes pkgFps cfg = foldl (\c (pkg,fp) -> addConfigDirectoryInclude pkg fp c) cfg pkgFps
addConfigDirectoryIncludePaths :: [FilePath] -> Config -> Config
addConfigDirectoryIncludePaths fps cfg = foldl (flip (addConfigDirectoryInclude Nothing)) cfg fps
configPackages :: Config -> [String]
configPackages = _configPackages
addConfigPackage :: String -> Config -> Config
addConfigPackage pkg cfg = cfg { _configPackages = pkg : _configPackages cfg }
addConfigPackages :: [String] -> Config -> Config
addConfigPackages fps cfg = foldl (flip addConfigPackage) cfg fps
shouldExportStrictWrapper :: ModuleName a -> Config -> Bool
shouldExportStrictWrapper (ModuleName _ m) cs = m `elem` configStrict cs