Skip to content

Commit

Permalink
Merge branch 'master' into 4125-cabal-style-build-tools
Browse files Browse the repository at this point in the history
  • Loading branch information
snoyberg authored Jul 9, 2018
2 parents d5b5f77 + 69349e1 commit 365fa7c
Show file tree
Hide file tree
Showing 6 changed files with 78 additions and 16 deletions.
6 changes: 6 additions & 0 deletions ChangeLog.md
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,9 @@ Behavior changes:
`cabal-install`, avoids some bugs, and opens up some possible
optimizations/laziness. See:
[#4125](https://github.com/commercialhaskell/stack/issues/4125).
* Mustache templating is not applied to large files (over 50kb) to
avoid performance degredation. See:
[#4133](https://github.com/commercialhaskell/stack/issues/4133).

Other enhancements:

Expand Down Expand Up @@ -66,6 +69,9 @@ Other enhancements:
download from a user other than `commercialstack` on Github, and can be prefixed
with the service `github:`, `gitlab:`, or `bitbucket:`.
* Switch to `githash` to include some unmerged bugfixes in `gitrev`
* [#3685](https://github.com/commercialhaskell/stack/issues/3685)
Suggestion to add `'allow-newer': true` now shows path to user config
file where this flag should be put into

Bug fixes:

Expand Down
8 changes: 5 additions & 3 deletions src/Stack/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -225,7 +225,8 @@ constructPlan ls0 baseConfigOpts0 locals extraToBuild0 localDumpPkgs loadPackage
else do
planDebug $ show errs
stackYaml <- view stackYamlL
prettyErrorNoIndent $ pprintExceptions errs stackYaml parents (wanted ctx)
stackRoot <- view stackRootL
prettyErrorNoIndent $ pprintExceptions errs stackYaml stackRoot parents (wanted ctx)
throwM $ ConstructPlanFailed "Plan construction failed."
where
hasBaseInDeps bconfig =
Expand Down Expand Up @@ -922,10 +923,11 @@ data BadDependency
pprintExceptions
:: [ConstructPlanException]
-> Path Abs File
-> Path Abs Dir
-> ParentMap
-> Set PackageName
-> AnsiDoc
pprintExceptions exceptions stackYaml parentMap wanted =
pprintExceptions exceptions stackYaml stackRoot parentMap wanted =
mconcat $
[ flow "While constructing the build plan, the following exceptions were encountered:"
, line <> line
Expand All @@ -935,7 +937,7 @@ pprintExceptions exceptions stackYaml parentMap wanted =
, line <> line
] ++
(if not onlyHasDependencyMismatches then [] else
[ " *" <+> align (flow "Set 'allow-newer: true' to ignore all version constraints and build anyway.")
[ " *" <+> align (flow "Set 'allow-newer: true' in " <+> toAnsiDoc (display (defaultUserConfigPath stackRoot)) <+> "to ignore all version constraints and build anyway.")
, line <> line
]
) ++
Expand Down
42 changes: 29 additions & 13 deletions src/Stack/New.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,15 +18,15 @@ module Stack.New

import Stack.Prelude
import Control.Monad.Trans.Writer.Strict
import qualified Data.ByteString as SB
import qualified Data.ByteString.Lazy as LB
import Data.Conduit
import Data.List
import qualified Data.Map.Strict as M
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Encoding as T
import qualified Data.Text.Encoding.Error as T (lenientDecode)
import qualified Data.Text.Lazy.Encoding as TLE
import Data.Time.Calendar
import Data.Time.Clock
import Network.HTTP.Download
Expand Down Expand Up @@ -140,7 +140,7 @@ loadTemplate name logIt = do
<> "\"")
exists <- doesFileExist path
if exists
then liftIO (fmap (T.decodeUtf8With T.lenientDecode) (SB.readFile (toFilePath path)))
then readFileUtf8 (toFilePath path)
else throwM (FailedToLoadTemplate name (toFilePath path))
relRequest :: Path Rel File -> Maybe Request
relRequest rel = do
Expand Down Expand Up @@ -195,17 +195,9 @@ applyTemplate project template nonceParams dir templateText = do
, ("name-as-module", nameAsModule) ]
configParams = configTemplateParams config
yearParam = M.singleton "year" currentYear
etemplateCompiled = Mustache.compileTemplate (T.unpack (templateName template)) templateText
templateCompiled <- case etemplateCompiled of
Left e -> throwM $ InvalidTemplate template (show e)
Right t -> return t
let (substitutionErrors, applied) = Mustache.checkedSubstitute templateCompiled context
missingKeys = S.fromList $ concatMap onlyMissingKeys substitutionErrors
unless (S.null missingKeys)
(logInfo ("\n" <> displayShow (MissingParameters project template missingKeys (configUserConfigPath config)) <> "\n"))
files :: Map FilePath LB.ByteString <-
catch (execWriterT $ runConduit $
yield (T.encodeUtf8 applied) .|
yield (T.encodeUtf8 templateText) .|
unpackTemplate receiveMem id
)
(\(e :: ProjectTemplateException) ->
Expand All @@ -217,12 +209,36 @@ applyTemplate project template nonceParams dir templateText = do
unless (any isPkgSpec . M.keys $ files) $
throwM (InvalidTemplate template "Template does not contain a .cabal \
\or package.yaml file")

-- Apply Mustache templating to a single file within the project
-- template.
let applyMustache bytes
-- Workaround for performance problems with mustache and
-- large files, applies to Yesod templates with large
-- bootstrap CSS files. See
-- https://github.com/commercialhaskell/stack/issues/4133.
| LB.length bytes < 50000
, Right text <- TLE.decodeUtf8' bytes = do
let etemplateCompiled = Mustache.compileTemplate (T.unpack (templateName template)) $ TL.toStrict text
templateCompiled <- case etemplateCompiled of
Left e -> throwM $ InvalidTemplate template (show e)
Right t -> return t
let (substitutionErrors, applied) = Mustache.checkedSubstitute templateCompiled context
missingKeys = S.fromList $ concatMap onlyMissingKeys substitutionErrors
unless (S.null missingKeys)
(logInfo ("\n" <> displayShow (MissingParameters project template missingKeys (configUserConfigPath config)) <> "\n"))
pure $ LB.fromStrict $ encodeUtf8 applied

-- Too large or too binary
| otherwise = pure bytes

liftM
M.fromList
(mapM
(\(fp,bytes) ->
do path <- parseRelFile fp
return (dir </> path, bytes))
bytes' <- applyMustache bytes
return (dir </> path, bytes'))
(M.toList files))
where
onlyMissingKeys (Mustache.VariableNotFound ks) = map T.unpack ks
Expand Down
23 changes: 23 additions & 0 deletions test/integration/tests/3685-config-yaml-for-allow-newer/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
import Control.Monad (unless)
import Data.List (isInfixOf)
import StackTest
import System.Directory

main :: IO ()
main = do
stack ["init", defaultResolverArg]
(_, stdErr) <- stackStderr ["install", "intero-0.1.23"]
-- here we check stderr for 'allow-newer: true' and
-- config.yaml sitting either on the same line or on
-- two consecutive lines
let errLines = lines stdErr
hasNewer l = "'allow-newer: true'" `isInfixOf` l
withNewer = map hasNewer errLines
userConfig = "config.yaml"
hasConfigForAllowNewer prevNewer l =
(prevNewer || hasNewer l) &&
userConfig `isInfixOf` l
hasProperLines =
or $ zipWith hasConfigForAllowNewer (False:withNewer) errLines
unless hasProperLines $
error $ "Not stderr lines with 'allow-newer: true' and " ++ userConfig
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
name: files
version: 0.1.0.0
build-type: Simple
cabal-version: >= 2.0

library
exposed-modules: Src
hs-source-dirs: src
build-depends: base
default-language: Haskell2010
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module Src where

-- | A function of the main library
funMainLib :: Int -> Int
funMainLib = succ

0 comments on commit 365fa7c

Please sign in to comment.