Skip to content

Commit

Permalink
Highlighter-friendly function signature formatting
Browse files Browse the repository at this point in the history
If :: follows the function name, Haskell Syntax Highlighting will recognise it as a function. This was already adopted in some modules. Now applied consistently.
  • Loading branch information
mpilgrem committed Dec 21, 2022
1 parent e1d9ad4 commit 8b0d1e2
Show file tree
Hide file tree
Showing 39 changed files with 301 additions and 290 deletions.
34 changes: 18 additions & 16 deletions src/Network/HTTP/StackClient.hs
Original file line number Diff line number Diff line change
Expand Up @@ -118,17 +118,19 @@ httpNoBody :: MonadIO m => Request -> m (Response ())
httpNoBody = Network.HTTP.Simple.httpNoBody . setUserAgent


httpSink
:: MonadUnliftIO m
httpSink ::
MonadUnliftIO m
=> Request
-> (Response () -> ConduitM Strict.ByteString Void m a)
-> m a
httpSink = Network.HTTP.Simple.httpSink . setUserAgent


withResponse
:: (MonadUnliftIO m, MonadIO n)
=> Request -> (Response (ConduitM i Strict.ByteString n ()) -> m a) -> m a
withResponse ::
(MonadUnliftIO m, MonadIO n)
=> Request
-> (Response (ConduitM i Strict.ByteString n ()) -> m a)
-> m a
withResponse = Network.HTTP.Simple.withResponse . setUserAgent

-- | Set the user-agent request header
Expand Down Expand Up @@ -169,19 +171,20 @@ redownload req dest = Download.redownload (setUserAgent req) dest
-- Throws VerifiedDownloadException.
-- Throws IOExceptions related to file system operations.
-- Throws HttpException.
verifiedDownload
:: HasTerm env
=> DownloadRequest
-> Path Abs File -- ^ destination
-> (Maybe Integer -> ConduitM ByteString Void (RIO env) ()) -- ^ custom hook to observe progress
-> RIO env Bool -- ^ Whether a download was performed
verifiedDownload ::
HasTerm env
=> DownloadRequest
-> Path Abs File -- ^ destination
-> (Maybe Integer -> ConduitM ByteString Void (RIO env) ())
-- ^ custom hook to observe progress
-> RIO env Bool -- ^ Whether a download was performed
verifiedDownload dr destpath progressSink =
Download.verifiedDownload dr' destpath progressSink
where
dr' = modifyRequest setUserAgent dr

verifiedDownloadWithProgress
:: HasTerm env
verifiedDownloadWithProgress ::
HasTerm env
=> DownloadRequest
-> Path Abs File
-> Text
Expand All @@ -190,9 +193,8 @@ verifiedDownloadWithProgress
verifiedDownloadWithProgress req destpath lbl msize =
verifiedDownload req destpath (chattyDownloadProgress lbl msize)


chattyDownloadProgress
:: ( HasLogFunc env
chattyDownloadProgress ::
( HasLogFunc env
, MonadIO m
, MonadReader env m
)
Expand Down
16 changes: 11 additions & 5 deletions src/Stack/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -162,7 +162,10 @@ build msetLocalFiles = do
(smtTargets $ smTargets sourceMap)
plan

buildLocalTargets :: HasEnvConfig env => NonEmpty Text -> RIO env (Either SomeException ())
buildLocalTargets ::
HasEnvConfig env
=> NonEmpty Text
-> RIO env (Either SomeException ())
buildLocalTargets targets =
tryAny $ withNewLocalBuildTargets (NE.toList targets) $ build Nothing

Expand All @@ -188,8 +191,11 @@ checkCabalVersion = do
CabalVersionNotSupported cabalVer

-- | See https://github.com/commercialhaskell/stack/issues/1198.
warnIfExecutablesWithSameNameCouldBeOverwritten
:: HasLogFunc env => [LocalPackage] -> Plan -> RIO env ()
warnIfExecutablesWithSameNameCouldBeOverwritten ::
HasLogFunc env
=> [LocalPackage]
-> Plan
-> RIO env ()
warnIfExecutablesWithSameNameCouldBeOverwritten locals plan = do
logDebug "Checking if we are going to build multiple executables with the same name"
forM_ (Map.toList warnings) $ \(exe,(toBuild,otherLocals)) -> do
Expand Down Expand Up @@ -290,8 +296,8 @@ mkBaseConfigOpts boptsCli = do
}

-- | Provide a function for loading package information from the package index
loadPackage
:: (HasBuildConfig env, HasSourceMap env)
loadPackage ::
(HasBuildConfig env, HasSourceMap env)
=> PackageLocationImmutable
-> Map FlagName Bool
-> [Text] -- ^ GHC options
Expand Down
8 changes: 4 additions & 4 deletions src/Stack/Build/Cache.hs
Original file line number Diff line number Diff line change
Expand Up @@ -200,8 +200,8 @@ writeCabalMod dir x = do
liftIO $ setFileTimes (toFilePath fp) x x

-- | See 'tryGetSetupConfigMod'
writeSetupConfigMod
:: HasEnvConfig env
writeSetupConfigMod ::
HasEnvConfig env
=> Path Abs Dir
-> Maybe CTime
-> RIO env ()
Expand All @@ -214,8 +214,8 @@ writeSetupConfigMod dir (Just x) = do
liftIO $ setFileTimes (toFilePath fp) x x

-- | See 'tryGetPackageProjectRoot'
writePackageProjectRoot
:: HasEnvConfig env
writePackageProjectRoot ::
HasEnvConfig env
=> Path Abs Dir
-> ByteString
-> RIO env ()
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1035,8 +1035,8 @@ psForceDirty :: PackageSource -> Bool
psForceDirty (PSFilePath lp) = lpForceDirty lp
psForceDirty PSRemote{} = False

psDirty
:: (MonadIO m, HasEnvConfig env, MonadReader env m)
psDirty ::
(MonadIO m, HasEnvConfig env, MonadReader env m)
=> PackageSource
-> m (Maybe (Set FilePath))
psDirty (PSFilePath lp) = runMemoizedWith $ lpDirtyFiles lp
Expand Down
20 changes: 10 additions & 10 deletions src/Stack/Build/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -137,8 +137,8 @@ loadSourceMap smt boptsCli sma = do
--
-- * Make sure things like profiling and haddocks are included in the hash
--
hashSourceMapData
:: (HasBuildConfig env, HasCompiler env)
hashSourceMapData ::
(HasBuildConfig env, HasCompiler env)
=> BuildOptsCLI
-> SourceMap
-> RIO env SourceMapHash
Expand Down Expand Up @@ -175,8 +175,8 @@ depPackageHashableContent DepPackage {..} = do
getUtf8Builder (mconcat cabalConfigOpts)

-- | All flags for a local package.
getLocalFlags
:: BuildOptsCLI
getLocalFlags ::
BuildOptsCLI
-> PackageName
-> Map FlagName Bool
getLocalFlags boptsCli name = Map.unions
Expand Down Expand Up @@ -412,8 +412,8 @@ checkBuildCache oldCache files = do
pure (Set.singleton fp, Map.singleton fp $ FileCacheInfo digest')

-- | Returns entries to add to the build cache for any newly found unlisted modules
addUnlistedToBuildCache
:: HasEnvConfig env
addUnlistedToBuildCache ::
HasEnvConfig env
=> Package
-> Path Abs File
-> Set NamedComponent
Expand All @@ -439,8 +439,8 @@ addUnlistedToBuildCache pkg cabalFP nonLibComponents buildCaches = do
-- | Gets list of Paths for files relevant to a set of components in a package.
-- Note that the library component, if any, is always automatically added to the
-- set of components.
getPackageFilesForTargets
:: HasEnvConfig env
getPackageFilesForTargets ::
HasEnvConfig env
=> Package
-> Path Abs File
-> Set NamedComponent
Expand Down Expand Up @@ -469,8 +469,8 @@ getFileDigestMaybe fp = do
getDigest src = runConduit $ src .| getZipSink (ZipSink SHA256.sinkHash)

-- | Get 'PackageConfig' for package given its name.
getPackageConfig
:: (HasBuildConfig env, HasSourceMap env)
getPackageConfig ::
(HasBuildConfig env, HasSourceMap env)
=> Map FlagName Bool
-> [Text] -- ^ GHC options
-> [Text] -- ^ cabal config opts
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Build/Target.hs
Original file line number Diff line number Diff line change
Expand Up @@ -397,8 +397,8 @@ resolveRawTarget sma allLocs (ri, rt) =
-- Combine the ResolveResults
---------------------------------------------------------------------------------

combineResolveResults
:: forall env. HasLogFunc env
combineResolveResults ::
forall env. HasLogFunc env
=> [ResolveResult]
-> RIO env ([Text], Map PackageName Target, Map PackageName PackageLocationImmutable)
combineResolveResults results = do
Expand Down
32 changes: 16 additions & 16 deletions src/Stack/BuildPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -147,8 +147,8 @@ gpdPackages = Map.fromList . map (toPair . C.package . C.packageDescription)
where
toPair (C.PackageIdentifier name version) = (name, version)

gpdPackageDeps
:: GenericPackageDescription
gpdPackageDeps ::
GenericPackageDescription
-> ActualCompiler
-> Platform
-> Map FlagName Bool
Expand Down Expand Up @@ -202,8 +202,8 @@ removeSrcPkgDefaultFlags gpds flags =
-- @GenericPackageDescription@ to compile against the given @BuildPlan@. Will
-- only modify non-manual flags, and will prefer default values for flags.
-- Returns the plan which produces least number of dep errors
selectPackageBuildPlan
:: Platform
selectPackageBuildPlan ::
Platform
-> ActualCompiler
-> Map PackageName Version
-> GenericPackageDescription
Expand Down Expand Up @@ -241,8 +241,8 @@ selectPackageBuildPlan platform compiler pool gpd =

-- | Check whether with the given set of flags a package's dependency
-- constraints can be satisfied against a given build plan or pool of packages.
checkPackageBuildPlan
:: Platform
checkPackageBuildPlan ::
Platform
-> ActualCompiler
-> Map PackageName Version
-> Map FlagName Bool
Expand All @@ -258,8 +258,8 @@ checkPackageBuildPlan platform compiler pool flags gpd =
-- | Checks if the given package dependencies can be satisfied by the given set
-- of packages. Will fail if a package is either missing or has a version
-- outside of the version range.
checkPackageDeps
:: PackageName -- ^ package using dependencies, for constructing DepErrors
checkPackageDeps ::
PackageName -- ^ package using dependencies, for constructing DepErrors
-> Map PackageName VersionRange -- ^ dependency constraints
-> Map PackageName Version -- ^ Available package pool or index
-> DepErrors
Expand Down Expand Up @@ -295,8 +295,8 @@ combineDepError (DepError a x) (DepError b y) =
-- build and an available package pool (snapshot) check whether the bundle's
-- dependencies can be satisfied. If flags is passed as Nothing flag settings
-- will be chosen automatically.
checkBundleBuildPlan
:: Platform
checkBundleBuildPlan ::
Platform
-> ActualCompiler
-> Map PackageName Version
-> Maybe (Map PackageName (Map FlagName Bool))
Expand Down Expand Up @@ -345,8 +345,8 @@ instance Show BuildPlanCheck where
-- | Check a set of 'GenericPackageDescription's and a set of flags against a
-- given snapshot. Returns how well the snapshot satisfies the dependencies of
-- the packages.
checkSnapBuildPlan
:: (HasConfig env, HasGHCVariant env)
checkSnapBuildPlan ::
(HasConfig env, HasGHCVariant env)
=> [ResolvedPath Dir]
-> Maybe (Map PackageName (Map FlagName Bool))
-> SnapshotCandidate env
Expand Down Expand Up @@ -385,8 +385,8 @@ checkSnapBuildPlan pkgDirs flags snapCandidate = do

-- | Find a snapshot and set of flags that is compatible with and matches as
-- best as possible with the given 'GenericPackageDescription's.
selectBestSnapshot
:: (HasConfig env, HasGHCVariant env)
selectBestSnapshot ::
(HasConfig env, HasGHCVariant env)
=> [ResolvedPath Dir]
-> NonEmpty SnapName
-> RIO env (SnapshotCandidate env, RawSnapshotLocation, BuildPlanCheck)
Expand Down Expand Up @@ -469,8 +469,8 @@ showPackageFlags pkg fl =
showMapPackages :: Map PackageName a -> Text
showMapPackages mp = showItems $ map packageNameString $ Map.keys mp

showCompilerErrors
:: Map PackageName (Map FlagName Bool)
showCompilerErrors ::
Map PackageName (Map FlagName Bool)
-> DepErrors
-> ActualCompiler
-> Text
Expand Down
Loading

0 comments on commit 8b0d1e2

Please sign in to comment.