module Stack.Types.Config where
import Control.Applicative ((<|>), (<$>), (<*>), pure)
import Control.Exception
import Control.Monad (liftM, mzero)
import Control.Monad.Catch (MonadThrow, throwM)
import Control.Monad.Reader (MonadReader, ask, asks, MonadIO, liftIO)
import Data.Aeson.Extended (ToJSON, toJSON, FromJSON, parseJSON, withText, withObject, object
,(.=), (.:?), (.!=), (.:), Value (String, Object))
import Data.Binary (Binary)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as S8
import Data.Either (partitionEithers)
import Data.Hashable (Hashable)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Monoid
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Encoding (encodeUtf8, decodeUtf8)
import Data.Typeable
import Data.Yaml (ParseException)
import Distribution.System (Platform)
import qualified Distribution.Text
import Distribution.Version (anyVersion, intersectVersionRanges)
import qualified Paths_stack as Meta
import Network.HTTP.Client (parseUrl)
import Path
import Stack.Types.BuildPlan (SnapName, renderSnapName, parseSnapName)
import Stack.Types.Docker
import Stack.Types.FlagName
import Stack.Types.PackageIdentifier
import Stack.Types.PackageName
import Stack.Types.Version
import System.Process.Read (EnvOverride)
data Config =
Config {configStackRoot :: !(Path Abs Dir)
,configDocker :: !DockerOpts
,configEnvOverride :: !(EnvSettings -> IO EnvOverride)
,configLocalPrograms :: !(Path Abs Dir)
,configConnectionCount :: !Int
,configHideTHLoading :: !Bool
,configPlatform :: !Platform
,configLatestSnapshotUrl :: !Text
,configPackageIndices :: ![PackageIndex]
,configSystemGHC :: !Bool
,configInstallGHC :: !Bool
,configLocalBin :: !(Path Abs Dir)
,configRequireStackVersion :: !VersionRange
,configJobs :: !Int
,configExtraIncludeDirs :: !(Set Text)
,configExtraLibDirs :: !(Set Text)
}
data PackageIndex = PackageIndex
{ indexName :: !IndexName
, indexLocation :: !IndexLocation
, indexDownloadPrefix :: !Text
, indexGpgVerify :: !Bool
, indexRequireHashes :: !Bool
}
deriving Show
instance FromJSON PackageIndex where
parseJSON = withObject "PackageIndex" $ \o -> do
name <- o .: "name"
prefix <- o .: "download-prefix"
mgit <- o .:? "git"
mhttp <- o .:? "http"
loc <-
case (mgit, mhttp) of
(Nothing, Nothing) -> fail $
"Must provide either Git or HTTP URL for " ++
T.unpack (indexNameText name)
(Just git, Nothing) -> return $ ILGit git
(Nothing, Just http) -> return $ ILHttp http
(Just git, Just http) -> return $ ILGitHttp git http
gpgVerify <- o .:? "gpg-verify" .!= False
reqHashes <- o .:? "require-hashes" .!= False
return PackageIndex
{ indexName = name
, indexLocation = loc
, indexDownloadPrefix = prefix
, indexGpgVerify = gpgVerify
, indexRequireHashes = reqHashes
}
newtype IndexName = IndexName { unIndexName :: ByteString }
deriving (Show, Eq, Ord, Hashable, Binary)
indexNameText :: IndexName -> Text
indexNameText = decodeUtf8 . unIndexName
instance ToJSON IndexName where
toJSON = toJSON . indexNameText
instance FromJSON IndexName where
parseJSON = withText "IndexName" $ \t ->
case parseRelDir (T.unpack t) of
Left e -> fail $ "Invalid index name: " ++ show e
Right _ -> return $ IndexName $ encodeUtf8 t
data IndexLocation = ILGit !Text | ILHttp !Text | ILGitHttp !Text !Text
deriving (Show, Eq, Ord)
data EnvSettings = EnvSettings
{ esIncludeLocals :: !Bool
, esIncludeGhcPackagePath :: !Bool
}
deriving (Show, Eq, Ord)
data BuildConfig = BuildConfig
{ bcConfig :: !Config
, bcResolver :: !Resolver
, bcGhcVersionExpected :: !Version
, bcPackages :: !(Map (Path Abs Dir) Bool)
, bcExtraDeps :: !(Map PackageName Version)
, bcRoot :: !(Path Abs Dir)
, bcStackYaml :: !(Path Abs File)
, bcFlags :: !(Map PackageName (Map FlagName Bool))
}
data EnvConfig = EnvConfig
{envConfigBuildConfig :: !BuildConfig
,envConfigCabalVersion :: !Version
,envConfigGhcVersion :: !Version}
instance HasBuildConfig EnvConfig where
getBuildConfig = envConfigBuildConfig
instance HasConfig EnvConfig
instance HasPlatform EnvConfig
instance HasStackRoot EnvConfig
class HasBuildConfig r => HasEnvConfig r where
getEnvConfig :: r -> EnvConfig
instance HasEnvConfig EnvConfig where
getEnvConfig = id
data LoadConfig m = LoadConfig
{ lcConfig :: !Config
, lcLoadBuildConfig :: !(Maybe Resolver -> NoBuildConfigStrategy -> m BuildConfig)
, lcProjectRoot :: !(Maybe (Path Abs Dir))
}
data NoBuildConfigStrategy
= ThrowException
| ExecStrategy
deriving (Show, Eq, Ord)
data PackageEntry = PackageEntry
{ peExtraDepMaybe :: !(Maybe Bool)
, peValidWanted :: !(Maybe Bool)
, peLocation :: !PackageLocation
, peSubdirs :: ![FilePath]
}
deriving Show
peExtraDep :: PackageEntry -> Bool
peExtraDep pe =
case peExtraDepMaybe pe of
Just x -> x
Nothing ->
case peValidWanted pe of
Just x -> not x
Nothing -> False
instance ToJSON PackageEntry where
toJSON pe | not (peExtraDep pe) && null (peSubdirs pe) =
toJSON $ peLocation pe
toJSON pe = object
[ "extra-dep" .= peExtraDep pe
, "location" .= peLocation pe
, "subdirs" .= peSubdirs pe
]
instance FromJSON PackageEntry where
parseJSON (String t) = do
loc <- parseJSON $ String t
return PackageEntry
{ peExtraDepMaybe = Nothing
, peValidWanted = Nothing
, peLocation = loc
, peSubdirs = []
}
parseJSON v = withObject "PackageEntry" (\o -> PackageEntry
<$> o .:? "extra-dep"
<*> o .:? "valid-wanted"
<*> o .: "location"
<*> o .:? "subdirs" .!= []) v
data PackageLocation
= PLFilePath FilePath
| PLHttpTarball Text
| PLGit Text Text
deriving Show
instance ToJSON PackageLocation where
toJSON (PLFilePath fp) = toJSON fp
toJSON (PLHttpTarball t) = toJSON t
toJSON (PLGit x y) = toJSON $ T.unwords ["git", x, y]
instance FromJSON PackageLocation where
parseJSON v = git v <|> withText "PackageLocation" (\t -> http t <|> file t) v
where
file t = pure $ PLFilePath $ T.unpack t
http t =
case parseUrl $ T.unpack t of
Left _ -> mzero
Right _ -> return $ PLHttpTarball t
git = withObject "PackageGitLocation" $ \o -> PLGit
<$> o .: "git"
<*> o .: "commit"
data Project = Project
{ projectPackages :: ![PackageEntry]
, projectExtraDeps :: !(Map PackageName Version)
, projectFlags :: !(Map PackageName (Map FlagName Bool))
, projectResolver :: !Resolver
}
deriving Show
instance ToJSON Project where
toJSON p = object
[ "packages" .= projectPackages p
, "extra-deps" .= map fromTuple (Map.toList $ projectExtraDeps p)
, "flags" .= projectFlags p
, "resolver" .= projectResolver p
]
data Resolver
= ResolverSnapshot SnapName
| ResolverGhc !MajorVersion
deriving (Show)
instance ToJSON Resolver where
toJSON = toJSON . renderResolver
instance FromJSON Resolver where
parseJSON = withText "Resolver" $
either (fail . show) return . parseResolver
renderResolver :: Resolver -> Text
renderResolver (ResolverSnapshot name) = renderSnapName name
renderResolver (ResolverGhc (MajorVersion x y)) = T.pack $ concat ["ghc-", show x, ".", show y]
parseResolver :: MonadThrow m => Text -> m Resolver
parseResolver t =
case parseSnapName t of
Right x -> return $ ResolverSnapshot x
Left _ ->
case parseGhc of
Just m -> return $ ResolverGhc m
Nothing -> throwM $ ParseResolverException t
where
parseGhc = T.stripPrefix "ghc-" t >>= parseMajorVersionFromString . T.unpack
class HasStackRoot env where
getStackRoot :: env -> Path Abs Dir
default getStackRoot :: HasConfig env => env -> Path Abs Dir
getStackRoot = configStackRoot . getConfig
class HasPlatform env where
getPlatform :: env -> Platform
default getPlatform :: HasConfig env => env -> Platform
getPlatform = configPlatform . getConfig
instance HasPlatform Platform where
getPlatform = id
class (HasStackRoot env, HasPlatform env) => HasConfig env where
getConfig :: env -> Config
default getConfig :: HasBuildConfig env => env -> Config
getConfig = bcConfig . getBuildConfig
instance HasStackRoot Config
instance HasPlatform Config
instance HasConfig Config where
getConfig = id
class HasConfig env => HasBuildConfig env where
getBuildConfig :: env -> BuildConfig
instance HasStackRoot BuildConfig
instance HasPlatform BuildConfig
instance HasConfig BuildConfig
instance HasBuildConfig BuildConfig where
getBuildConfig = id
data ConfigMonoid =
ConfigMonoid
{ configMonoidDockerOpts :: !DockerOptsMonoid
, configMonoidConnectionCount :: !(Maybe Int)
, configMonoidHideTHLoading :: !(Maybe Bool)
, configMonoidLatestSnapshotUrl :: !(Maybe Text)
, configMonoidPackageIndices :: !(Maybe [PackageIndex])
, configMonoidSystemGHC :: !(Maybe Bool)
,configMonoidInstallGHC :: !(Maybe Bool)
,configMonoidRequireStackVersion :: !VersionRange
,configMonoidOS :: !(Maybe String)
,configMonoidArch :: !(Maybe String)
,configMonoidJobs :: !(Maybe Int)
,configMonoidExtraIncludeDirs :: !(Set Text)
,configMonoidExtraLibDirs :: !(Set Text)
}
deriving Show
instance Monoid ConfigMonoid where
mempty = ConfigMonoid
{ configMonoidDockerOpts = mempty
, configMonoidConnectionCount = Nothing
, configMonoidHideTHLoading = Nothing
, configMonoidLatestSnapshotUrl = Nothing
, configMonoidPackageIndices = Nothing
, configMonoidSystemGHC = Nothing
, configMonoidInstallGHC = Nothing
, configMonoidRequireStackVersion = anyVersion
, configMonoidOS = Nothing
, configMonoidArch = Nothing
, configMonoidJobs = Nothing
, configMonoidExtraIncludeDirs = Set.empty
, configMonoidExtraLibDirs = Set.empty
}
mappend l r = ConfigMonoid
{ configMonoidDockerOpts = configMonoidDockerOpts l <> configMonoidDockerOpts r
, configMonoidConnectionCount = configMonoidConnectionCount l <|> configMonoidConnectionCount r
, configMonoidHideTHLoading = configMonoidHideTHLoading l <|> configMonoidHideTHLoading r
, configMonoidLatestSnapshotUrl = configMonoidLatestSnapshotUrl l <|> configMonoidLatestSnapshotUrl r
, configMonoidPackageIndices = configMonoidPackageIndices l <|> configMonoidPackageIndices r
, configMonoidSystemGHC = configMonoidSystemGHC l <|> configMonoidSystemGHC r , configMonoidInstallGHC = configMonoidInstallGHC l <|> configMonoidInstallGHC r
, configMonoidRequireStackVersion = intersectVersionRanges (configMonoidRequireStackVersion l)
(configMonoidRequireStackVersion r)
, configMonoidOS = configMonoidOS l <|> configMonoidOS r
, configMonoidArch = configMonoidArch l <|> configMonoidArch r
, configMonoidJobs = configMonoidJobs l <|> configMonoidJobs r
, configMonoidExtraIncludeDirs = Set.union (configMonoidExtraIncludeDirs l) (configMonoidExtraIncludeDirs r)
, configMonoidExtraLibDirs = Set.union (configMonoidExtraLibDirs l) (configMonoidExtraLibDirs r)
}
instance FromJSON ConfigMonoid where
parseJSON =
withObject "ConfigMonoid" $
\obj ->
do configMonoidDockerOpts <- obj .:? T.pack "docker" .!= mempty
configMonoidConnectionCount <- obj .:? "connection-count"
configMonoidHideTHLoading <- obj .:? "hide-th-loading"
configMonoidLatestSnapshotUrl <- obj .:? "latest-snapshot-url"
configMonoidPackageIndices <- obj .:? "package-indices"
configMonoidSystemGHC <- obj .:? "system-ghc"
configMonoidInstallGHC <- obj .:? "install-ghc"
configMonoidRequireStackVersion <- unVersionRangeJSON <$>
obj .:? "require-stack-version"
.!= VersionRangeJSON anyVersion
configMonoidOS <- obj .:? "os"
configMonoidArch <- obj .:? "arch"
configMonoidJobs <- obj .:? "jobs"
configMonoidExtraIncludeDirs <- obj .:? "extra-include-dirs" .!= Set.empty
configMonoidExtraLibDirs <- obj .:? "extra-lib-dirs" .!= Set.empty
return ConfigMonoid {..}
newtype VersionRangeJSON = VersionRangeJSON { unVersionRangeJSON :: VersionRange }
instance FromJSON VersionRangeJSON where
parseJSON = withText "VersionRange"
(\s -> maybe (fail ("Invalid cabal-style VersionRange: " ++ T.unpack s))
(return . VersionRangeJSON)
(Distribution.Text.simpleParse (T.unpack s)))
data ConfigException
= ParseConfigFileException (Path Abs File) ParseException
| ParseResolverException Text
| NoProjectConfigFound (Path Abs Dir) (Maybe Text)
| UnexpectedTarballContents [Path Abs Dir] [Path Abs File]
| BadStackVersionException VersionRange
| NoMatchingSnapshot [SnapName]
deriving Typeable
instance Show ConfigException where
show (ParseConfigFileException configFile exception) = concat
[ "Could not parse '"
, toFilePath configFile
, "':\n"
, show exception
, "\nSee https://github.com/commercialhaskell/stack/wiki/stack.yaml."
]
show (ParseResolverException t) = concat
[ "Invalid resolver value: "
, T.unpack t
, ". Possible valid values include lts-2.12, nightly-YYYY-MM-DD, and ghc-7.10. "
, "See https://www.stackage.org/snapshots for a complete list."
]
show (NoProjectConfigFound dir mcmd) = concat
[ "Unable to find a stack.yaml file in the current directory ("
, toFilePath dir
, ") or its ancestors"
, case mcmd of
Nothing -> ""
Just cmd -> "\nRecommended action: stack " ++ T.unpack cmd
]
show (UnexpectedTarballContents dirs files) = concat
[ "When unpacking a tarball specified in your stack.yaml file, "
, "did not find expected contents. Expected: a single directory. Found: "
, show ( map (toFilePath . dirname) dirs
, map (toFilePath . filename) files
)
]
show (BadStackVersionException requiredRange) = concat
[ "The version of stack you are using ("
, show (fromCabalVersion Meta.version)
, ") is outside the required\n"
,"version range ("
, T.unpack (versionRangeText requiredRange)
, ") specified in stack.yaml." ]
show (NoMatchingSnapshot names) = concat
[ "There was no snapshot found that matched the package "
, "bounds in your .cabal files.\n"
, "Please choose one of the following commands to get started.\n\n"
, unlines $ map
(\name -> " stack init --resolver " ++ T.unpack (renderSnapName name))
names
, "\nYou'll then need to add some extra-deps. See:\n\n"
, " https://github.com/commercialhaskell/stack/wiki/stack.yaml#extra-deps"
, "\n\nYou can also try falling back to a dependency solver with:\n\n"
, " stack init --solver"
]
instance Exception ConfigException
askConfig :: (MonadReader env m, HasConfig env) => m Config
askConfig = liftM getConfig ask
askLatestSnapshotUrl :: (MonadReader env m, HasConfig env) => m Text
askLatestSnapshotUrl = asks (configLatestSnapshotUrl . getConfig)
configPackageIndexRoot :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs Dir)
configPackageIndexRoot (IndexName name) = do
config <- asks getConfig
dir <- parseRelDir $ S8.unpack name
return (configStackRoot config </> $(mkRelDir "indices") </> dir)
configPackageIndexCache :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File)
configPackageIndexCache = liftM (</> $(mkRelFile "00-index.cache")) . configPackageIndexRoot
configPackageIndex :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File)
configPackageIndex = liftM (</> $(mkRelFile "00-index.tar")) . configPackageIndexRoot
configPackageIndexGz :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File)
configPackageIndexGz = liftM (</> $(mkRelFile "00-index.tar.gz")) . configPackageIndexRoot
configPackageTarball :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> PackageIdentifier -> m (Path Abs File)
configPackageTarball iname ident = do
root <- configPackageIndexRoot iname
name <- parseRelDir $ packageNameString $ packageIdentifierName ident
ver <- parseRelDir $ versionString $ packageIdentifierVersion ident
base <- parseRelFile $ packageIdentifierString ident ++ ".tar.gz"
return (root </> $(mkRelDir "packages") </> name </> ver </> base)
workDirRel :: Path Rel Dir
workDirRel = $(mkRelDir ".stack-work")
configProjectWorkDir :: (HasBuildConfig env, MonadReader env m) => m (Path Abs Dir)
configProjectWorkDir = do
bc <- asks getBuildConfig
return (bcRoot bc </> workDirRel)
configInstalledCache :: (HasBuildConfig env, MonadReader env m) => m (Path Abs File)
configInstalledCache = liftM (</> $(mkRelFile "installed-cache.bin")) configProjectWorkDir
platformRelDir :: (MonadReader env m, HasPlatform env, MonadThrow m) => m (Path Rel Dir)
platformRelDir = asks getPlatform >>= parseRelDir . Distribution.Text.display
configShakeFilesDir :: (MonadReader env m, HasBuildConfig env) => m (Path Abs Dir)
configShakeFilesDir = liftM (</> $(mkRelDir "shake")) configProjectWorkDir
configLocalUnpackDir :: (MonadReader env m, HasBuildConfig env) => m (Path Abs Dir)
configLocalUnpackDir = liftM (</> $(mkRelDir "unpacked")) configProjectWorkDir
snapshotsDir :: (MonadReader env m, HasConfig env, MonadThrow m) => m (Path Abs Dir)
snapshotsDir = do
config <- asks getConfig
platform <- platformRelDir
return $ configStackRoot config </> $(mkRelDir "snapshots") </> platform
installationRootDeps :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
installationRootDeps = do
snapshots <- snapshotsDir
bc <- asks getBuildConfig
ec <- asks getEnvConfig
name <- parseRelDir $ T.unpack $ renderResolver $ bcResolver bc
ghc <- parseRelDir $ versionString $ envConfigGhcVersion ec
return $ snapshots </> name </> ghc
installationRootLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
installationRootLocal = do
bc <- asks getBuildConfig
ec <- asks getEnvConfig
name <- parseRelDir $ T.unpack $ renderResolver $ bcResolver bc
ghc <- parseRelDir $ versionString $ envConfigGhcVersion ec
platform <- platformRelDir
return $ configProjectWorkDir bc </> $(mkRelDir "install") </> platform </> name </> ghc
packageDatabaseDeps :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
packageDatabaseDeps = do
root <- installationRootDeps
return $ root </> $(mkRelDir "pkgdb")
packageDatabaseLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
packageDatabaseLocal = do
root <- installationRootLocal
return $ root </> $(mkRelDir "pkgdb")
flagCacheLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
flagCacheLocal = do
root <- installationRootLocal
return $ root </> $(mkRelDir "flag-cache")
configMiniBuildPlanCache :: (MonadThrow m, MonadReader env m, HasStackRoot env, HasPlatform env)
=> SnapName
-> m (Path Abs File)
configMiniBuildPlanCache name = do
root <- asks getStackRoot
platform <- platformRelDir
file <- parseRelFile $ T.unpack (renderSnapName name) ++ ".cache"
return (root </> $(mkRelDir "build-plan-cache") </> platform </> file)
bindirSuffix :: Path Rel Dir
bindirSuffix = $(mkRelDir "bin")
docdirSuffix :: Path Rel Dir
docdirSuffix = $(mkRelDir "doc")
extraBinDirs :: (MonadThrow m, MonadReader env m, HasEnvConfig env)
=> m (Bool -> [Path Abs Dir])
extraBinDirs = do
deps <- installationRootDeps
local <- installationRootLocal
return $ \locals -> if locals
then [local </> bindirSuffix, deps </> bindirSuffix]
else [deps </> bindirSuffix]
getMinimalEnvOverride :: (MonadReader env m, HasConfig env, MonadIO m) => m EnvOverride
getMinimalEnvOverride = do
config <- asks getConfig
liftIO $ configEnvOverride config EnvSettings
{ esIncludeLocals = False
, esIncludeGhcPackagePath = False
}
data ProjectAndConfigMonoid
= ProjectAndConfigMonoid !Project !ConfigMonoid
instance FromJSON ProjectAndConfigMonoid where
parseJSON = withObject "Project, ConfigMonoid" $ \o -> do
dirs <- o .:? "packages" .!= [packageEntryCurrDir]
extraDeps' <- o .:? "extra-deps" .!= []
extraDeps <-
case partitionEithers $ goDeps extraDeps' of
([], x) -> return $ Map.fromList x
(errs, _) -> fail $ unlines errs
flags <- o .:? "flags" .!= mempty
resolver <- o .: "resolver"
config <- parseJSON $ Object o
let project = Project
{ projectPackages = dirs
, projectExtraDeps = extraDeps
, projectFlags = flags
, projectResolver = resolver
}
return $ ProjectAndConfigMonoid project config
where
goDeps =
map toSingle . Map.toList . Map.unionsWith Set.union . map toMap
where
toMap i = Map.singleton
(packageIdentifierName i)
(Set.singleton (packageIdentifierVersion i))
toSingle (k, s) =
case Set.toList s of
[x] -> Right (k, x)
xs -> Left $ concat
[ "Multiple versions for package "
, packageNameString k
, ": "
, unwords $ map versionString xs
]
packageEntryCurrDir :: PackageEntry
packageEntryCurrDir = PackageEntry
{ peValidWanted = Nothing
, peExtraDepMaybe = Nothing
, peLocation = PLFilePath "."
, peSubdirs = []
}