Skip to content

Commit 91769ab

Browse files
authored
Merge pull request #10613 from cabalism/typos/in-hs-files
Fix typos in `*.hs` files
2 parents daa6ffa + 02a9724 commit 91769ab

File tree

32 files changed

+60
-60
lines changed

32 files changed

+60
-60
lines changed

Cabal-syntax/src/Distribution/Backpack.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -70,7 +70,7 @@ import qualified Data.Set as Set
7070
-- represent it as a 'DefiniteUnitId uid'.
7171
--
7272
-- For a source component using Backpack, however, there is more
73-
-- structure as components may be parametrized over some signatures, and
73+
-- structure as components may be parameterized over some signatures, and
7474
-- these \"holes\" may be partially or wholly filled.
7575
--
7676
-- OpenUnitId plays an important role when we are mix-in linking,

Cabal-syntax/src/Distribution/Fields/Field.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66

77
-- | Cabal-like file AST types: 'Field', 'Section' etc
88
--
9-
-- These types are parametrized by an annotation.
9+
-- These types are parameterized by an annotation.
1010
module Distribution.Fields.Field
1111
( -- * Cabal file
1212
Field (..)

Cabal-syntax/src/Distribution/Fields/LexerMonad.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ toPWarnings =
9494
Just $ PWarning PWTLexTab (NE.head poss) $ "Tabs used as indentation at " ++ intercalate ", " (NE.toList $ fmap showPos poss)
9595
toWarning LexInconsistentIndentation poss =
9696
Just $ PWarning PWTInconsistentIndentation (NE.head poss) $ "Inconsistent indentation. Indentation jumps at lines " ++ intercalate ", " (NE.toList $ fmap (show . positionRow) poss)
97-
-- LexBraces warning about using { } delimeters is not reported as parser warning.
97+
-- LexBraces warning about using { } delimiters is not reported as parser warning.
9898
toWarning LexBraces _ =
9999
Nothing
100100

Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -679,7 +679,7 @@ processImports v fromBuildInfo commonStanzas = go []
679679
fields' <- catMaybes <$> traverse (warnImport v) fields
680680
pure $ (fields', \x -> foldr (mergeCommonStanza fromBuildInfo) x acc)
681681

682-
-- | Warn on "import" fields, also map to Maybe, so errorneous fields can be filtered
682+
-- | Warn on "import" fields, also map to Maybe, so erroneous fields can be filtered
683683
warnImport :: CabalSpecVersion -> Field Position -> ParseResult (Maybe (Field Position))
684684
warnImport v (Field (Name pos name) _) | name == "import" = do
685685
if specHasCommonStanzas v == NoCommonStanzas

Cabal-syntax/src/Distribution/SPDX/LicenseId.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -677,7 +677,7 @@ data LicenseId
677677
deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data)
678678

679679
instance Binary LicenseId where
680-
-- Word16 is encoded in big endianess
680+
-- Word16 is encoded in big endianness
681681
-- https://github.com/kolmodin/binary/blob/master/src/Data/Binary/Class.hs#L220-LL227
682682
put = Binary.putWord16be . fromIntegral . fromEnum
683683
get = do

Cabal-syntax/src/Distribution/Types/VersionInterval.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,7 @@ isVersion0 = (==) version0
9595
stage1 :: VersionRange -> [VersionInterval]
9696
stage1 = cataVersionRange alg
9797
where
98-
-- version range leafs transform into singleton intervals
98+
-- version range leaves transform into singleton intervals
9999
alg (ThisVersionF v) = [VersionInterval (LowerBound v InclusiveBound) (UpperBound v InclusiveBound)]
100100
alg (LaterVersionF v) = [VersionInterval (LowerBound v ExclusiveBound) NoUpperBound]
101101
alg (OrLaterVersionF v) = [VersionInterval (LowerBound v InclusiveBound) NoUpperBound]

Cabal-tests/tests/ParserTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -140,7 +140,7 @@ errorTest fp = cabalGoldenTest fp correct $ do
140140

141141
return $ toUTF8BS $ case x of
142142
Right gpd ->
143-
"UNXPECTED SUCCESS\n" ++
143+
"UNEXPECTED SUCCESS\n" ++
144144
showGenericPackageDescription gpd
145145
Left (v, errs) ->
146146
unlines $ ("VERSION: " ++ show v) : map (showPError fp) (NE.toList errs)

Cabal-tests/tests/UnitTests/Distribution/SPDX.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,7 @@ shouldReject = map License
9191
--
9292
-- * "WITH exc" exceptions are rejected
9393
--
94-
-- * There should be a way to interpert license as (conjunction of)
94+
-- * There should be a way to interpret license as (conjunction of)
9595
-- OSI-accepted licenses or CC0
9696
--
9797
isAcceptableLicense :: License -> Bool

Cabal/src/Distribution/GetOpt.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -134,11 +134,11 @@ zipDefault ad bd (a : as) (b : bs) = (a, b) : zipDefault ad bd as bs
134134
-- | Pretty printing of short options.
135135
-- * With required arguments can be given as:
136136
-- @-w PATH or -wPATH (but not -w=PATH)@
137-
-- This is dislayed as:
137+
-- This is displayed as:
138138
-- @-w PATH or -wPATH@
139139
-- * With optional but default arguments can be given as:
140140
-- @-j or -jNUM (but not -j=NUM or -j NUM)@
141-
-- This is dislayed as:
141+
-- This is displayed as:
142142
-- @-j[NUM]@
143143
fmtShort :: ArgDescr a -> Char -> String
144144
fmtShort (NoArg _) so = "-" ++ [so]
@@ -152,11 +152,11 @@ fmtShort (OptArg _ _ ad) so =
152152
-- | Pretty printing of long options.
153153
-- * With required arguments can be given as:
154154
-- @--with-compiler=PATH (but not --with-compiler PATH)@
155-
-- This is dislayed as:
155+
-- This is displayed as:
156156
-- @--with-compiler=PATH@
157157
-- * With optional but default arguments can be given as:
158158
-- @--jobs or --jobs=NUM (but not --jobs NUM)@
159-
-- This is dislayed as:
159+
-- This is displayed as:
160160
-- @--jobs[=NUM]@
161161
fmtLong :: ArgDescr a -> String -> String
162162
fmtLong (NoArg _) lo = "--" ++ lo

Cabal/src/Distribution/PackageDescription/Check/Common.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,7 @@ partitionDeps ads ns ds = do
7979
-- shared targets that match
8080
fads = filter (flip elem dqs . fst) ads
8181
-- the names of such targets
82-
inNam = nub $ map fst fads :: [UnqualComponentName]
82+
inName = nub $ map fst fads :: [UnqualComponentName]
8383
-- the dependencies of such targets
8484
inDep = concatMap snd fads :: [Dependency]
8585

@@ -96,7 +96,7 @@ partitionDeps ads ns ds = do
9696
-- text, ← no warning, inherited
9797
-- monadacme ← warning!
9898
let fFun d =
99-
notElem (unqualName d) inNam
99+
notElem (unqualName d) inName
100100
&& notElem
101101
(unqualName d)
102102
(map unqualName inDep)
@@ -116,7 +116,7 @@ partitionDeps ads ns ds = do
116116
-- for important dependencies like base).
117117
checkPVP
118118
:: Monad m
119-
=> (String -> PackageCheck) -- Warn message dependend on name
119+
=> (String -> PackageCheck) -- Warn message depends on name
120120
-- (e.g. "base", "Cabal").
121121
-> [Dependency]
122122
-> CheckM m ()

Cabal/src/Distribution/PackageDescription/Check/Monad.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -242,7 +242,7 @@ tellCM ck = do
242242
-- There are some errors which, even though severe, will
243243
-- be allowed by Hackage *if* under a non-default flag.
244244
isErrAllowable :: PackageCheck -> Bool
245-
isErrAllowable c = case extractCheckExplantion c of
245+
isErrAllowable c = case extractCheckExplanation c of
246246
(WErrorUnneeded _) -> True
247247
(JUnneeded _) -> True
248248
(FDeferTypeErrorsUnneeded _) -> True

Cabal/src/Distribution/PackageDescription/Check/Warning.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ module Distribution.PackageDescription.Check.Warning
2525
, ppPackageCheck
2626
, ppCheckExplanationId
2727
, isHackageDistError
28-
, extractCheckExplantion
28+
, extractCheckExplanation
2929
, filterPackageChecksById
3030
, filterPackageChecksByIdString
3131
) where
@@ -124,7 +124,7 @@ filterPackageChecksById cs is = filter ff cs
124124
ff c =
125125
flip notElem is
126126
. checkExplanationId
127-
. extractCheckExplantion
127+
. extractCheckExplanation
128128
$ c
129129

130130
-- | Filter Package Check by Check explanation /string/.
@@ -293,14 +293,14 @@ data CheckExplanation
293293
-- to be a ad hoc monoid.
294294

295295
-- Convenience.
296-
extractCheckExplantion :: PackageCheck -> CheckExplanation
297-
extractCheckExplantion (PackageBuildImpossible e) = e
298-
extractCheckExplantion (PackageBuildWarning e) = e
299-
extractCheckExplantion (PackageDistSuspicious e) = e
300-
extractCheckExplantion (PackageDistSuspiciousWarn e) = e
301-
extractCheckExplantion (PackageDistInexcusable e) = e
296+
extractCheckExplanation :: PackageCheck -> CheckExplanation
297+
extractCheckExplanation (PackageBuildImpossible e) = e
298+
extractCheckExplanation (PackageBuildWarning e) = e
299+
extractCheckExplanation (PackageDistSuspicious e) = e
300+
extractCheckExplanation (PackageDistSuspiciousWarn e) = e
301+
extractCheckExplanation (PackageDistInexcusable e) = e
302302

303-
-- | Identifier for the speficic 'CheckExplanation'. This ensures `--ignore`
303+
-- | Identifier for the specific 'CheckExplanation'. This ensures `--ignore`
304304
-- can output a warning on unrecognised values.
305305
-- ☞ N.B.: should be kept in sync with 'CheckExplanation'.
306306
data CheckExplanationID
@@ -590,7 +590,7 @@ type CheckExplanationIDString = String
590590

591591
-- A one-word identifier for each CheckExplanation
592592
--
593-
-- ☞ N.B: if you modify anything here, remeber to change the documentation
593+
-- ☞ N.B: if you modify anything here, remember to change the documentation
594594
-- in @doc/cabal-commands.rst@!
595595
ppCheckExplanationId :: CheckExplanationID -> CheckExplanationIDString
596596
ppCheckExplanationId CIParseWarning = "parser-warning"

Cabal/src/Distribution/Simple/Build/PackageInfoModule.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@
1010
-- Generating the PackageInfo_pkgname module.
1111
--
1212
-- This is a module that Cabal generates for the benefit of packages. It
13-
-- enables them to find their package informations.
13+
-- enables them to find their package information.
1414
module Distribution.Simple.Build.PackageInfoModule
1515
( generatePackageInfoModule
1616
) where

Cabal/src/Distribution/Simple/BuildToolDepends.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ import qualified Data.Map as Map
1313
import Distribution.Package
1414
import Distribution.PackageDescription
1515

16-
-- | Same as 'desugarBuildTool', but requires atomic informations (package
16+
-- | Same as 'desugarBuildTool', but requires atomic information (package
1717
-- name, executable names) instead of a whole 'PackageDescription'.
1818
desugarBuildToolSimple
1919
:: PackageName

Cabal/src/Distribution/Simple/Command.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -624,8 +624,8 @@ data Command action
624624
-- | Mark command as hidden. Hidden commands don't show up in the 'progname
625625
-- help' or 'progname --help' output.
626626
hiddenCommand :: Command action -> Command action
627-
hiddenCommand (Command name synopsys f _cmdType) =
628-
Command name synopsys f HiddenCommand
627+
hiddenCommand (Command name synopsis f _cmdType) =
628+
Command name synopsis f HiddenCommand
629629

630630
commandAddAction
631631
:: CommandUI flags

Cabal/src/Distribution/Simple/Compiler.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -482,7 +482,7 @@ waySupported :: String -> Compiler -> Maybe Bool
482482
waySupported way comp =
483483
case compilerFlavor comp of
484484
GHC ->
485-
-- Infomation about compiler ways is only accurately reported after
485+
-- Information about compiler ways is only accurately reported after
486486
-- 9.10.1. Which is useful as this is before profiling dynamic support
487487
-- was introduced. (See GHC #24881)
488488
if compilerVersion comp >= mkVersion [9, 10, 1]

Cabal/src/Distribution/Simple/Program/Types.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -143,7 +143,7 @@ data ConfiguredProgram = ConfiguredProgram
143143
, programMonitorFiles :: [FilePath]
144144
-- ^ In addition to the 'programLocation' where the program was found,
145145
-- these are additional locations that were looked at. The combination
146-
-- of ths found location and these not-found locations can be used to
146+
-- of this found location and these not-found locations can be used to
147147
-- monitor to detect when the re-configuring the program might give a
148148
-- different result (e.g. found in a different location).
149149
}

Cabal/src/Distribution/Simple/Setup/Config.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1102,7 +1102,7 @@ configureArgs bcHack flags =
11021102
(Flag hc, NoFlag) -> [hc_flag_name ++ prettyShow hc]
11031103
(NoFlag, NoFlag) -> []
11041104
hc_flag_name
1105-
-- TODO kill off thic bc hack when defaultUserHooks is removed.
1105+
-- TODO kill off this bc hack when defaultUserHooks is removed.
11061106
| bcHack = "--with-hc="
11071107
| otherwise = "--with-compiler="
11081108
optFlag name config_field = case config_field flags of

Cabal/src/Distribution/Simple/SetupHooks/Rule.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -723,7 +723,7 @@ on the build-system side, we don't have access to any of the types, and thus don
723723
how much to read in order to reconstruct the associated opaque 'ByteString'.
724724
To ensure we always serialise/deserialise including the length of the data,
725725
the 'ScopedArgument' newtype is used, with a custom 'Binary' instance that always
726-
incldues the length. We use this newtype:
726+
includes the length. We use this newtype:
727727
728728
- in the definition of 'CommandData', for arguments to rules,
729729
- in the definition of 'DepsRes', for the result of dynamic dependency computations.

Cabal/src/Distribution/Simple/Utils.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -388,7 +388,7 @@ die' verbosity msg = withFrozenCallStack $ do
388388
=<< pure . addErrorPrefix
389389
=<< prefixWithProgName msg
390390

391-
-- Type which will be a wrapper for cabal -expections and cabal-install exceptions
391+
-- Type which will be a wrapper for cabal -exceptions and cabal-install exceptions
392392
data VerboseException a = VerboseException CallStack POSIXTime Verbosity a
393393
deriving (Show, Typeable)
394394

Cabal/src/Distribution/Types/LocalBuildInfo.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -447,7 +447,7 @@ buildWays lbi =
447447
let
448448
-- enable-library-profiling (enable (static profiling way)) .p_o
449449
-- enable-shared (enabled dynamic way) .dyn_o
450-
-- enable-profiling-shared (enable dyanmic profilng way) .p_dyn_o
450+
-- enable-profiling-shared (enable dynamic profilng way) .p_dyn_o
451451
-- enable-library-vanilla (enable vanilla way) .o
452452
--
453453
-- enable-executable-dynamic => build dynamic executables

Cabal/src/Distribution/Utils/IOData.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ instance KnownIODataMode LBS.ByteString where
8080

8181
-- | 'IOData' Wrapper for 'System.IO.hPutStr' and 'System.IO.hClose'
8282
--
83-
-- This is the dual operation ot 'hGetIODataContents',
83+
-- This is the dual operation to 'hGetIODataContents',
8484
-- and consequently the handle is closed with `hClose`.
8585
--
8686
-- /Note:/ this performs lazy-IO.

cabal-install-solver/tests/UnitTests/Distribution/Solver/Modular/MessageUtils.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -58,9 +58,9 @@ isOutOfBounds :: Int -> String -> String -> Bool
5858
isOutOfBounds range a b = not $ withinRange range a b
5959

6060
testRange :: Int -> [String] -> String -> Assertion
61-
testRange range elems erronousElement = assertBool "String should be out of bounds to make a spelling suggestion" (isOutOfBounds range erronousElement suggestion)
61+
testRange range elems erroneousElement = assertBool "String should be out of bounds to make a spelling suggestion" (isOutOfBounds range erroneousElement suggestion)
6262
where
63-
suggestion = mostSimilarElement erronousElement elems
63+
suggestion = mostSimilarElement erroneousElement elems
6464

6565
outOfBounds :: [String]
6666
outOfBounds =

cabal-install/src/Distribution/Client/Check.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,7 @@ readGenericPackageDescriptionCheck verbosity fpath = do
5757
dieWithException verbosity ParseError
5858
Right x -> return (warnings, x)
5959

60-
-- | Checks a packge for common errors. Returns @True@ if the package
60+
-- | Checks a package for common errors. Returns @True@ if the package
6161
-- is fit to upload to Hackage, @False@ otherwise.
6262
-- Note: must be called with the CWD set to the directory containing
6363
-- the '.cabal' file.

cabal-install/src/Distribution/Client/CmdInstall.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -390,7 +390,7 @@ installAction flags@NixStyleFlags{extraFlags, configFlags, installFlags, project
390390
-- NOTE: CmdInstall and project local packages.
391391
--
392392
-- CmdInstall always installs packages from a source distribution that, in case of unpackage
393-
-- pacakges, is created automatically. This is implemented in getSpecsAndTargetSelectors.
393+
-- packages, is created automatically. This is implemented in getSpecsAndTargetSelectors.
394394
--
395395
-- This has the inconvenience that the planner will consider all packages as non-local
396396
-- (see `ProjectPlanning.shouldBeLocal`) and that any project or cli configuration will
@@ -1031,7 +1031,7 @@ installLibraries
10311031

10321032
-- See ticket #8894. This is safe to include any nonreinstallable boot pkg,
10331033
-- but the particular package users will always expect to be in scope without specific installation
1034-
-- is base, so that they can access prelude, regardles of if they specifically asked for it.
1034+
-- is base, so that they can access prelude, regardless of if they specifically asked for it.
10351035
globalPackages :: [PackageName]
10361036
globalPackages = mkPackageName <$> ["base"]
10371037

cabal-install/src/Distribution/Client/CmdRepl.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -408,7 +408,7 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
408408

409409
return (buildCtx, compiler, configureReplOptions & lReplOptionsFlags %~ (++ repl_flags), targets)
410410

411-
-- Multi Repl implemention see: https://well-typed.com/blog/2023/03/cabal-multi-unit/ for
411+
-- Multi Repl implementation see: https://well-typed.com/blog/2023/03/cabal-multi-unit/ for
412412
-- a high-level overview about how everything fits together.
413413
if Set.size (distinctTargetComponents targets) > 1
414414
then withTempDirectoryEx verbosity tempFileOptions distDir "multi-out" $ \dir' -> do
@@ -440,7 +440,7 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
440440
let sp = intercalate [searchPathSeparator] (map fst (sortBy (comparing @Int snd) $ Map.toList (combine_search_paths all_paths)))
441441
-- HACK: Just combine together all env overrides, placing the most common things last
442442

443-
-- ghc program with overriden PATH
443+
-- ghc program with overridden PATH
444444
(ghcProg, _) <- requireProgram verbosity ghcProgram (pkgConfigCompilerProgs (elaboratedShared buildCtx'))
445445
let ghcProg' = ghcProg{programOverrideEnv = [("PATH", Just sp)]}
446446

cabal-install/src/Distribution/Client/IndexUtils/ActiveRepos.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -168,7 +168,7 @@ organizeByRepos
168168
-> [a]
169169
-> Either String [(a, CombineStrategy)]
170170
organizeByRepos (ActiveRepos xs0) sel ys0 =
171-
-- here we use lazyness to do only one traversal
171+
-- here we use laziness to do only one traversal
172172
let (rest, result) = case go rest xs0 ys0 of
173173
Right (rest', result') -> (rest', Right result')
174174
Left err -> ([], Left err)

cabal-install/src/Distribution/Client/JobControl.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -174,7 +174,7 @@ readAllTChan qvar = go []
174174
Nothing -> return (reverse xs)
175175
Just x -> go (x : xs)
176176

177-
-- | Make a 'JobControl' where the parallism is controlled by a semaphore.
177+
-- | Make a 'JobControl' where the parallelism is controlled by a semaphore.
178178
--
179179
-- This uses the GHC -jsem option to allow GHC to take additional semaphore slots
180180
-- if we are not using them all.

cabal-install/src/Distribution/Client/ProjectPlanning.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -632,7 +632,7 @@ rebuildInstallPlan
632632

633633
-- Configuring other programs.
634634
--
635-
-- Having configred the compiler, now we configure all the remaining
635+
-- Having configured the compiler, now we configure all the remaining
636636
-- programs. This is to check we can find them, and to monitor them for
637637
-- changes.
638638
--
@@ -902,7 +902,7 @@ reportPlanningFailure projectConfig comp platform pkgSpecifiers =
902902
buildReports
903903
platform
904904
where
905-
-- TODO may want to handle the projectConfigLogFile paramenter here, or just remove it entirely?
905+
-- TODO may want to handle the projectConfigLogFile parameter here, or just remove it entirely?
906906

907907
reportFailure = Cabal.fromFlag . projectConfigReportPlanningFailure . projectConfigBuildOnly $ projectConfig
908908
pkgids = mapMaybe theSpecifiedPackage pkgSpecifiers

cabal-install/src/Distribution/Client/ScriptUtils.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -414,8 +414,8 @@ withTemporaryTempDirectory act = newEmptyMVar >>= \m -> bracket (getMkTmp m) (rm
414414
return tmpDir
415415
rmTmp m _ = tryTakeMVar m >>= maybe (return ()) (handleDoesNotExist () . removeDirectoryRecursive)
416416

417-
scriptComponenetName :: IsString s => FilePath -> s
418-
scriptComponenetName scriptPath = fromString cname
417+
scriptComponentName :: IsString s => FilePath -> s
418+
scriptComponentName scriptPath = fromString cname
419419
where
420420
cname = "script-" ++ map censor (takeFileName scriptPath)
421421
censor c
@@ -437,7 +437,7 @@ scriptDistDirParams scriptPath ctx compiler platform =
437437
, distParamOptimization = fromFlagOrDefault NormalOptimisation optimization
438438
}
439439
where
440-
cn = scriptComponenetName scriptPath
440+
cn = scriptComponentName scriptPath
441441
cid = mkComponentId $ prettyShow fakePackageId <> "-inplace-" <> prettyShow cn
442442
optimization = (packageConfigOptimization . projectConfigLocalPackages . projectConfig) ctx
443443

@@ -475,7 +475,7 @@ updateContextAndWriteProjectFile ctx scriptPath scriptExecutable = do
475475
sourcePackage =
476476
fakeProjectSourcePackage projectRoot
477477
& lSrcpkgDescription . L.condExecutables
478-
.~ [(scriptComponenetName scriptPath, CondNode executable (targetBuildDepends $ buildInfo executable) [])]
478+
.~ [(scriptComponentName scriptPath, CondNode executable (targetBuildDepends $ buildInfo executable) [])]
479479
executable =
480480
scriptExecutable
481481
& L.modulePath .~ absScript

0 commit comments

Comments
 (0)