11{-# LANGUAGE NoImplicitPrelude #-}
2- {-# LANGUAGE LambdaCase #-}
32{-# LANGUAGE OverloadedStrings #-}
43
54-- | Build the project.
@@ -19,8 +18,8 @@ import Data.List.Extra ( groupSort )
1918import qualified Data.Map as Map
2019import qualified Data.Set as Set
2120import qualified Data.Text as T
22- import qualified Distribution.PackageDescription as C
23- import Distribution.Types.Dependency ( Dependency (.. ), depLibraries )
21+ -- import qualified Distribution.PackageDescription as C
22+ -- import Distribution.Types.Dependency ( Dependency (..), depLibraries )
2423import Distribution.Version ( mkVersion )
2524import RIO.NonEmpty ( nonEmpty )
2625import qualified RIO.NonEmpty as NE
@@ -63,11 +62,12 @@ import Stack.Types.GlobalOpts ( globalOptsBuildOptsMonoidL )
6362import Stack.Types.NamedComponent ( exeComponents )
6463import Stack.Types.Package
6564 ( InstallLocation (.. ), LocalPackage (.. ), Package (.. )
66- , PackageConfig (.. ), lpFiles , lpFilesForComponents )
65+ , PackageConfig (.. ), lpFiles , lpFilesForComponents
66+ )
6767import Stack.Types.Platform ( HasPlatform (.. ) )
6868import Stack.Types.Runner ( Runner , globalOptsL )
6969import Stack.Types.SourceMap
70- ( CommonPackage ( .. ), ProjectPackage ( .. ), SMTargets (.. )
70+ ( SMTargets (.. )
7171 , SourceMap (.. ), Target (.. ) )
7272import System.Terminal ( fixCodePage )
7373
@@ -138,8 +138,6 @@ build msetLocalFiles = do
138138 depsLocals <- localDependencies
139139 let allLocals = locals <> depsLocals
140140
141- checkSubLibraryDependencies (Map. elems $ smProject sourceMap)
142-
143141 boptsCli <- view $ envConfigL. to envConfigBuildOptsCLI
144142 -- Set local files, necessary for file watching
145143 stackYaml <- view stackYamlL
@@ -371,34 +369,3 @@ checkComponentsBuildable lps =
371369 | lp <- lps
372370 , c <- Set. toList (lpUnbuildable lp)
373371 ]
374-
375- -- | Find if any sub-library dependency (other than internal libraries) exists
376- -- in each project package.
377- checkSubLibraryDependencies :: HasTerm env => [ProjectPackage ] -> RIO env ()
378- checkSubLibraryDependencies projectPackages =
379- forM_ projectPackages $ \ projectPackage -> do
380- C. GenericPackageDescription pkgDesc _ _ lib subLibs foreignLibs exes tests benches <-
381- liftIO $ cpGPD . ppCommon $ projectPackage
382-
383- let pName = pkgName . C. package $ pkgDesc
384- dependencies = concatMap getDeps subLibs <>
385- concatMap getDeps foreignLibs <>
386- concatMap getDeps exes <>
387- concatMap getDeps tests <>
388- concatMap getDeps benches <>
389- maybe [] C. condTreeConstraints lib
390- notInternal (Dependency pName' _ _) = pName' /= pName
391- publicDependencies = filter notInternal dependencies
392- publicLibraries = concatMap (toList . depLibraries) publicDependencies
393-
394- when (subLibDepExist publicLibraries) $
395- prettyWarnS
396- " Sublibrary dependency is not supported, this will almost certainly \
397- \fail."
398- where
399- getDeps (_, C. CondNode _ dep _) = dep
400- subLibDepExist = any
401- ( \ case
402- C. LSubLibName _ -> True
403- C. LMainLibName -> False
404- )
0 commit comments