Skip to content

Commit a1dee53

Browse files
committed
Various light reformatting
1 parent c3faf5c commit a1dee53

File tree

21 files changed

+518
-484
lines changed

21 files changed

+518
-484
lines changed

src/Data/Attoparsec/Args.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -37,8 +37,8 @@ argsParser mode = many (P.skipSpace *> (quoted <|> unquoted)) <*
3737
unquoted = P.many1 naked
3838
quoted = P.char '"' *> str <* P.char '"'
3939
str = many ( case mode of
40-
Escaping -> escaped <|> nonquote
41-
NoEscaping -> nonquote
40+
Escaping -> escaped <|> nonquote
41+
NoEscaping -> nonquote
4242
)
4343
escaped = P.char '\\' *> P.anyChar
4444
nonquote = P.satisfy (/= '"')

src/Data/Attoparsec/Combinators.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,11 @@ module Data.Attoparsec.Combinators
1111
import Stack.Prelude
1212

1313
-- | Concatenate two parsers.
14-
appending :: (Applicative f, Semigroup a)
15-
=> f a -> f a -> f a
14+
appending ::
15+
(Applicative f, Semigroup a)
16+
=> f a
17+
-> f a
18+
-> f a
1619
appending a b = (<>) <$> a <*> b
1720

1821
-- | Alternative parsers.

src/Options/Applicative/Builder/Extra.hs

Lines changed: 16 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -345,21 +345,24 @@ pathCompleterWith PathCompleterOpts {..} = mkCompleter $ \inputRaw -> do
345345
| input == "" && pcoAbsolute -> pure ["/"]
346346
| otherwise -> pure []
347347
Just searchDir -> do
348-
entries <- getDirectoryContents searchDir `catch` \(_ :: IOException) -> pure []
348+
entries <-
349+
getDirectoryContents searchDir `catch` \(_ :: IOException) -> pure []
349350
fmap catMaybes $ forM entries $ \entry ->
350351
-- Skip . and .. unless user is typing . or ..
351-
if entry `elem` ["..", "."] && searchPrefix `notElem` ["..", "."] then pure Nothing else
352-
if searchPrefix `isPrefixOf` entry
353-
then do
354-
let path = searchDir </> entry
355-
case (pcoFileFilter path, pcoDirFilter path) of
356-
(True, True) -> pure $ Just (inputSearchDir </> entry)
357-
(fileAllowed, dirAllowed) -> do
358-
isDir <- doesDirectoryExist path
359-
if (if isDir then dirAllowed else fileAllowed)
360-
then pure $ Just (inputSearchDir </> entry)
361-
else pure Nothing
362-
else pure Nothing
352+
if entry `elem` ["..", "."] && searchPrefix `notElem` ["..", "."]
353+
then pure Nothing
354+
else
355+
if searchPrefix `isPrefixOf` entry
356+
then do
357+
let path = searchDir </> entry
358+
case (pcoFileFilter path, pcoDirFilter path) of
359+
(True, True) -> pure $ Just (inputSearchDir </> entry)
360+
(fileAllowed, dirAllowed) -> do
361+
isDir <- doesDirectoryExist path
362+
if (if isDir then dirAllowed else fileAllowed)
363+
then pure $ Just (inputSearchDir </> entry)
364+
else pure Nothing
365+
else pure Nothing
363366

364367
unescapeBashArg :: String -> String
365368
unescapeBashArg ('\'' : rest) = rest

src/Path/Extended.hs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,8 @@
11
module Path.Extended
2-
( fileExtension
3-
, addExtension
4-
, replaceExtension
5-
) where
2+
( fileExtension
3+
, addExtension
4+
, replaceExtension
5+
) where
66

77
import Control.Monad.Catch
88
import qualified Path
@@ -11,13 +11,15 @@ import Path (Path, File)
1111
fileExtension :: MonadThrow m => Path b File -> m String
1212
fileExtension = Path.fileExtension
1313

14-
addExtension :: MonadThrow m
14+
addExtension ::
15+
MonadThrow m
1516
=> String
1617
-> Path b File
1718
-> m (Path b File)
1819
addExtension = Path.addExtension
1920

20-
replaceExtension :: MonadThrow m
21+
replaceExtension ::
22+
MonadThrow m
2123
=> String
2224
-> Path b File
2325
-> m (Path b File)

src/Path/Extra.hs

Lines changed: 13 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -50,8 +50,13 @@ parseCollapsedAbsFile = parseAbsFile . collapseFilePath
5050
-- | Add a relative FilePath to the end of a Path
5151
-- We can't parse the FilePath first because we need to account for ".."
5252
-- in the FilePath (#2895)
53-
concatAndCollapseAbsDir :: MonadThrow m => Path Abs Dir -> FilePath -> m (Path Abs Dir)
54-
concatAndCollapseAbsDir base rel = parseCollapsedAbsDir (toFilePath base FP.</> rel)
53+
concatAndCollapseAbsDir ::
54+
MonadThrow m
55+
=> Path Abs Dir
56+
-> FilePath
57+
-> m (Path Abs Dir)
58+
concatAndCollapseAbsDir base rel =
59+
parseCollapsedAbsDir (toFilePath base FP.</> rel)
5560

5661
-- | Collapse intermediate "." and ".." directories from a path.
5762
--
@@ -96,15 +101,17 @@ dropRoot (Path l) = Path (FP.dropDrive l)
96101
--
97102
-- > forgivingAbsence (resolveFile …) >>= rejectMissingFile
98103

99-
rejectMissingFile :: MonadIO m
104+
rejectMissingFile ::
105+
MonadIO m
100106
=> Maybe (Path Abs File)
101107
-> m (Maybe (Path Abs File))
102108
rejectMissingFile Nothing = pure Nothing
103109
rejectMissingFile (Just p) = bool Nothing (Just p) <$> doesFileExist p
104110

105111
-- | See 'rejectMissingFile'.
106112

107-
rejectMissingDir :: MonadIO m
113+
rejectMissingDir ::
114+
MonadIO m
108115
=> Maybe (Path Abs Dir)
109116
-> m (Maybe (Path Abs Dir))
110117
rejectMissingDir Nothing = pure Nothing
@@ -122,4 +129,5 @@ pathToText :: Path b t -> T.Text
122129
pathToText = T.pack . toFilePath
123130

124131
tryGetModificationTime :: MonadIO m => Path Abs File -> m (Either () UTCTime)
125-
tryGetModificationTime = liftIO . tryJust (guard . isDoesNotExistError) . getModificationTime
132+
tryGetModificationTime =
133+
liftIO . tryJust (guard . isDoesNotExistError) . getModificationTime

src/Path/Find.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -19,18 +19,18 @@ import System.PosixCompat.Files
1919
( getSymbolicLinkStatus, isSymbolicLink )
2020

2121
-- | Find the location of a file matching the given predicate.
22-
findFileUp :: (MonadIO m,MonadThrow m)
23-
=> Path Abs Dir -- ^ Start here.
24-
-> (Path Abs File -> Bool) -- ^ Predicate to match the file.
25-
-> Maybe (Path Abs Dir) -- ^ Do not ascend above this directory.
26-
-> m (Maybe (Path Abs File)) -- ^ Absolute file path.
22+
findFileUp :: (MonadIO m, MonadThrow m)
23+
=> Path Abs Dir -- ^ Start here.
24+
-> (Path Abs File -> Bool) -- ^ Predicate to match the file.
25+
-> Maybe (Path Abs Dir) -- ^ Do not ascend above this directory.
26+
-> m (Maybe (Path Abs File)) -- ^ Absolute file path.
2727
findFileUp = findPathUp snd
2828

2929
-- | Find the location of a directory matching the given predicate.
3030
findDirUp :: (MonadIO m,MonadThrow m)
31-
=> Path Abs Dir -- ^ Start here.
32-
-> (Path Abs Dir -> Bool) -- ^ Predicate to match the directory.
33-
-> Maybe (Path Abs Dir) -- ^ Do not ascend above this directory.
31+
=> Path Abs Dir -- ^ Start here.
32+
-> (Path Abs Dir -> Bool) -- ^ Predicate to match the directory.
33+
-> Maybe (Path Abs Dir) -- ^ Do not ascend above this directory.
3434
-> m (Maybe (Path Abs Dir)) -- ^ Absolute directory path.
3535
findDirUp = findPathUp fst
3636

src/Stack/Build/ConstructPlan.hs

Lines changed: 36 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -112,13 +112,14 @@ data AddDepRes
112112
data W = W
113113
{ wFinals :: !(Map PackageName (Either ConstructPlanException Task))
114114
, wInstall :: !(Map Text InstallLocation)
115-
-- ^ executable to be installed, and location where the binary is placed
115+
-- ^ executable to be installed, and location where the binary is placed
116116
, wDirty :: !(Map PackageName Text)
117-
-- ^ why a local package is considered dirty
117+
-- ^ why a local package is considered dirty
118118
, wWarnings :: !([Text] -> [Text])
119-
-- ^ Warnings
119+
-- ^ Warnings
120120
, wParents :: !ParentMap
121-
-- ^ Which packages a given package depends on, along with the package's version
121+
-- ^ Which packages a given package depends on, along with the package's
122+
-- version
122123
}
123124
deriving Generic
124125

@@ -188,22 +189,20 @@ instance HasCompiler Ctx where
188189
instance HasEnvConfig Ctx where
189190
envConfigL = lens ctxEnvConfig (\x y -> x { ctxEnvConfig = y })
190191

191-
-- | Computes a build plan. This means figuring out which build 'Task's
192-
-- to take, and the interdependencies among the build 'Task's. In
193-
-- particular:
192+
-- | Computes a build plan. This means figuring out which build 'Task's to take,
193+
-- and the interdependencies among the build 'Task's. In particular:
194194
--
195-
-- 1) It determines which packages need to be built, based on the
196-
-- transitive deps of the current targets. For local packages, this is
197-
-- indicated by the 'lpWanted' boolean. For extra packages to build,
198-
-- this comes from the @extraToBuild0@ argument of type @Set
199-
-- PackageName@. These are usually packages that have been specified on
200-
-- the commandline.
195+
-- 1) It determines which packages need to be built, based on the transitive
196+
-- deps of the current targets. For local packages, this is indicated by the
197+
-- 'lpWanted' boolean. For extra packages to build, this comes from the
198+
-- @extraToBuild0@ argument of type @Set PackageName@. These are usually
199+
-- packages that have been specified on the command line.
201200
--
202-
-- 2) It will only rebuild an upstream package if it isn't present in
203-
-- the 'InstalledMap', or if some of its dependencies have changed.
201+
-- 2) It will only rebuild an upstream package if it isn't present in the
202+
-- 'InstalledMap', or if some of its dependencies have changed.
204203
--
205-
-- 3) It will only rebuild a local package if its files are dirty or
206-
-- some of its dependencies have changed.
204+
-- 3) It will only rebuild a local package if its files are dirty or some of its
205+
-- dependencies have changed.
207206
constructPlan ::
208207
forall env. HasEnvConfig env
209208
=> BaseConfigOpts
@@ -374,14 +373,14 @@ data UnregisterState = UnregisterState
374373
-- already registered local packages
375374
mkUnregisterLocal ::
376375
Map PackageName Task
377-
-- ^ Tasks
376+
-- ^ Tasks
378377
-> Map PackageName Text
379-
-- ^ Reasons why packages are dirty and must be rebuilt
378+
-- ^ Reasons why packages are dirty and must be rebuilt
380379
-> [DumpPackage]
381-
-- ^ Local package database dump
380+
-- ^ Local package database dump
382381
-> Bool
383-
-- ^ If true, we're doing a special initialBuildSteps build - don't unregister
384-
-- target packages.
382+
-- ^ If true, we're doing a special initialBuildSteps build - don't
383+
-- unregister target packages.
385384
-> Map GhcPkgId (PackageIdentifier, Text)
386385
mkUnregisterLocal tasks dirtyReason localDumpPkgs initialBuildSteps =
387386
-- We'll take multiple passes through the local packages. This
@@ -764,8 +763,8 @@ installPackageGivenDeps isAllInOne buildHaddocks ps package minstalled
764763
packageBuildTypeConfig :: Package -> Bool
765764
packageBuildTypeConfig pkg = packageBuildType pkg == Configure
766765

767-
-- Update response in the lib map. If it is an error, and there's
768-
-- already an error about cyclic dependencies, prefer the cyclic error.
766+
-- Update response in the lib map. If it is an error, and there's already an
767+
-- error about cyclic dependencies, prefer the cyclic error.
769768
updateLibMap :: PackageName -> Either ConstructPlanException AddDepRes -> M ()
770769
updateLibMap name val = modify $ \mp ->
771770
case (M.lookup name mp, val) of
@@ -778,15 +777,14 @@ addEllipsis t
778777
| otherwise = T.take 97 t <> "..."
779778

780779
-- | Given a package, recurses into all of its dependencies. The results
781-
-- indicate which packages are missing, meaning that their 'GhcPkgId's
782-
-- will be figured out during the build, after they've been built. The
783-
-- 2nd part of the tuple result indicates the packages that are already
784-
-- installed which will be used.
780+
-- indicate which packages are missing, meaning that their 'GhcPkgId's will be
781+
-- figured out during the build, after they've been built. The 2nd part of the
782+
-- tuple result indicates the packages that are already installed which will be
783+
-- used.
785784
--
786-
-- The 3rd part of the tuple is an 'InstallLocation'. If it is 'Local',
787-
-- then the parent package must be installed locally. Otherwise, if it
788-
-- is 'Snap', then it can either be installed locally or in the
789-
-- snapshot.
785+
-- The 3rd part of the tuple is an 'InstallLocation'. If it is 'Local', then the
786+
-- parent package must be installed locally. Otherwise, if it is 'Snap', then it
787+
-- can either be installed locally or in the snapshot.
790788
addPackageDeps ::
791789
Package
792790
-> M ( Either
@@ -977,10 +975,10 @@ checkDirtiness ps installed package present buildHaddocks = do
977975
<> addEllipsis (T.pack $ unwords $ Set.toList files)
978976
Nothing -> Nothing
979977
case mreason of
980-
Nothing -> pure False
981-
Just reason -> do
982-
tell mempty { wDirty = Map.singleton (packageName package) reason }
983-
pure True
978+
Nothing -> pure False
979+
Just reason -> do
980+
tell mempty { wDirty = Map.singleton (packageName package) reason }
981+
pure True
984982

985983
describeConfigDiff :: Config -> ConfigCache -> ConfigCache -> Maybe Text
986984
describeConfigDiff config old new
@@ -1027,8 +1025,8 @@ describeConfigDiff config old new
10271025

10281026
userOpts = filter (not . isStackOpt)
10291027
. (if configRebuildGhcOptions config
1030-
then id
1031-
else stripGhcOptions)
1028+
then id
1029+
else stripGhcOptions)
10321030
. map T.pack
10331031
. (\(ConfigureOpts x y) -> x ++ y)
10341032
. configCacheOpts

src/Stack/Build/Execute.hs

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -940,9 +940,14 @@ toActions installedMap mtestLock runInBase ee (mbuild, mfinal) =
940940
beopts = boptsBenchmarkOpts bopts
941941

942942
-- | Generate the ConfigCache
943-
getConfigCache :: HasEnvConfig env
944-
=> ExecuteEnv -> Task -> InstalledMap -> Bool -> Bool
945-
-> RIO env (Map PackageIdentifier GhcPkgId, ConfigCache)
943+
getConfigCache ::
944+
HasEnvConfig env
945+
=> ExecuteEnv
946+
-> Task
947+
-> InstalledMap
948+
-> Bool
949+
-> Bool
950+
-> RIO env (Map PackageIdentifier GhcPkgId, ConfigCache)
946951
getConfigCache ExecuteEnv {..} task@Task {..} installedMap enableTest enableBench = do
947952
let extra =
948953
-- We enable tests if the test suite dependencies are already

src/Stack/Build/Source.hs

Lines changed: 23 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -8,15 +8,15 @@
88

99
-- Load information on package sources
1010
module Stack.Build.Source
11-
( projectLocalPackages
12-
, localDependencies
13-
, loadCommonPackage
14-
, loadLocalPackage
15-
, loadSourceMap
16-
, getLocalFlags
17-
, addUnlistedToBuildCache
18-
, hashSourceMapData
19-
) where
11+
( projectLocalPackages
12+
, localDependencies
13+
, loadCommonPackage
14+
, loadLocalPackage
15+
, loadSourceMap
16+
, getLocalFlags
17+
, addUnlistedToBuildCache
18+
, hashSourceMapData
19+
) where
2020

2121
import Conduit ( ZipSink (..), withSourceFile )
2222
import Data.ByteString.Builder ( toLazyByteString )
@@ -171,8 +171,11 @@ hashSourceMapData boptsCli sm = do
171171
-- resolver 'ghc-X.Y.Z' is used, no extra-deps and e.g. user wants builds
172172
-- with profiling or without
173173
bootGhcOpts = map display (generalGhcOptions bc boptsCli False False)
174-
hashedContent = toLazyByteString $ compilerPath <> compilerInfo <>
175-
getUtf8Builder (mconcat bootGhcOpts) <> mconcat immDeps
174+
hashedContent =
175+
toLazyByteString $ compilerPath
176+
<> compilerInfo
177+
<> getUtf8Builder (mconcat bootGhcOpts)
178+
<> mconcat immDeps
176179
pure $ SourceMapHash (SHA256.hashLazyBytes hashedContent)
177180

178181
depPackageHashableContent :: (HasConfig env) => DepPackage -> RIO env Builder
@@ -181,9 +184,9 @@ depPackageHashableContent DepPackage {..} =
181184
PLMutable _ -> pure ""
182185
PLImmutable pli -> do
183186
let flagToBs (f, enabled) =
184-
if enabled
185-
then ""
186-
else "-" <> fromString (C.unFlagName f)
187+
if enabled
188+
then ""
189+
else "-" <> fromString (C.unFlagName f)
187190
flags = map flagToBs $ Map.toList (cpFlags dpCommon)
188191
ghcOptions = map display (cpGhcOptions dpCommon)
189192
cabalConfigOpts = map display (cpCabalConfigOpts dpCommon)
@@ -396,12 +399,12 @@ loadLocalPackage pp = do
396399
, lpCabalFile = ppCabalFP pp
397400
, lpWanted = isWanted
398401
, lpComponents = nonLibComponents
399-
-- TODO: refactor this so that it's easier to be sure that these
400-
-- components are indeed unbuildable.
401-
--
402-
-- The reasoning here is that if the STLocalComps specification made it
403-
-- through component parsing, but the components aren't present, then they
404-
-- must not be buildable.
402+
-- TODO: refactor this so that it's easier to be sure that these
403+
-- components are indeed unbuildable.
404+
--
405+
-- The reasoning here is that if the STLocalComps specification made it
406+
-- through component parsing, but the components aren't present, then they
407+
-- must not be buildable.
405408
, lpUnbuildable = toComponents
406409
(exes `Set.difference` packageExes pkg)
407410
(tests `Set.difference` Map.keysSet (packageTests pkg))

0 commit comments

Comments
 (0)