diff --git a/Cabal-QuickCheck/src/Test/QuickCheck/GenericArbitrary.hs b/Cabal-QuickCheck/src/Test/QuickCheck/GenericArbitrary.hs index fdfe817a70c..00f32bc0d70 100644 --- a/Cabal-QuickCheck/src/Test/QuickCheck/GenericArbitrary.hs +++ b/Cabal-QuickCheck/src/Test/QuickCheck/GenericArbitrary.hs @@ -14,7 +14,7 @@ import Test.QuickCheck import Control.Applicative (pure, (<$>), (<*>)) #endif --- Generic arbitary for non-recursive types +-- Generic arbitrary for non-recursive types genericArbitrary :: (Generic a, GArbitrary (Rep a)) => Gen a genericArbitrary = fmap to garbitrary diff --git a/Cabal-described/src/Distribution/Utils/CharSet.hs b/Cabal-described/src/Distribution/Utils/CharSet.hs index c5c906d9ffe..45bfbb1300b 100644 --- a/Cabal-described/src/Distribution/Utils/CharSet.hs +++ b/Cabal-described/src/Distribution/Utils/CharSet.hs @@ -2,7 +2,7 @@ {-# LANGUAGE CPP #-} -- | Sets of characters. -- --- Using this is more efficint than 'RE.Type.Alt':ng individual characters. +-- Using this is more efficient than 'RE.Type.Alt':ng individual characters. module Distribution.Utils.CharSet ( -- * Set of characters CharSet, diff --git a/Cabal-syntax/README.md b/Cabal-syntax/README.md index 1ec4f6b47f2..cb99814a198 100644 --- a/Cabal-syntax/README.md +++ b/Cabal-syntax/README.md @@ -32,8 +32,8 @@ Cabal's users what their most pressing problems are with Cabal and [Hackage]. You may have a favourite Cabal bug or limitation. Look at Cabal's [bug tracker]. Ensure that the problem is reported there and adequately described. Comment on the issue to report how much of a -problem the bug is for you. Subscribe to the issues's notifications to -discussed requirements and keep informed on progress. For feature +problem the bug is for you. Subscribe to the issue's notifications to +discuss requirements and keep informed on progress. For feature requests, it is helpful if there is a description of how you would expect to interact with the new feature. diff --git a/Cabal-syntax/src/Distribution/Compat/CharParsing.hs b/Cabal-syntax/src/Distribution/Compat/CharParsing.hs index 67f46533fd3..ebe77119249 100644 --- a/Cabal-syntax/src/Distribution/Compat/CharParsing.hs +++ b/Cabal-syntax/src/Distribution/Compat/CharParsing.hs @@ -346,7 +346,7 @@ munch1 :: CharParsing m => (Char -> Bool) -> m String munch1 = some . satisfy {-# INLINE munch1 #-} --- | Greedely munch characters while predicate holds. +-- | Greedily munch characters while predicate holds. -- Always succeeds. munch :: CharParsing m => (Char -> Bool) -> m String munch = many . satisfy diff --git a/Cabal-syntax/src/Distribution/Compat/Newtype.hs b/Cabal-syntax/src/Distribution/Compat/Newtype.hs index adf75366e4c..904e2e5d4b3 100644 --- a/Cabal-syntax/src/Distribution/Compat/Newtype.hs +++ b/Cabal-syntax/src/Distribution/Compat/Newtype.hs @@ -3,7 +3,7 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} -- | Per Conor McBride, the 'Newtype' typeclass represents the packing and --- unpacking of a newtype, and allows you to operatate under that newtype with +-- unpacking of a newtype, and allows you to operate under that newtype with -- functions such as 'ala'. module Distribution.Compat.Newtype ( Newtype (..), diff --git a/Cabal-syntax/src/Distribution/FieldGrammar.hs b/Cabal-syntax/src/Distribution/FieldGrammar.hs index c30de94d71d..f75cea2a5e0 100644 --- a/Cabal-syntax/src/Distribution/FieldGrammar.hs +++ b/Cabal-syntax/src/Distribution/FieldGrammar.hs @@ -17,7 +17,7 @@ module Distribution.FieldGrammar ( PrettyFieldGrammar, PrettyFieldGrammar', prettyFieldGrammar, - -- * Auxlilary + -- * Auxiliary (^^^), Section(..), Fields, diff --git a/Cabal-syntax/src/Distribution/Fields.hs b/Cabal-syntax/src/Distribution/Fields.hs index 88addc88a77..18b0aa6d92c 100644 --- a/Cabal-syntax/src/Distribution/Fields.hs +++ b/Cabal-syntax/src/Distribution/Fields.hs @@ -1,4 +1,4 @@ --- | Utilitiies to work with @.cabal@ like file structure. +-- | Utilities to work with @.cabal@ like file structure. module Distribution.Fields ( -- * Types Field(..), diff --git a/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs b/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs index 1e38664f413..6b0a90d9ee2 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs @@ -855,7 +855,7 @@ libFieldNames :: [FieldName] libFieldNames = fieldGrammarKnownFieldList (libraryFieldGrammar LMainLibName) ------------------------------------------------------------------------------- --- Suplementary build information +-- Supplementary build information ------------------------------------------------------------------------------- parseHookedBuildInfo :: BS.ByteString -> ParseResult HookedBuildInfo diff --git a/Cabal-syntax/src/Distribution/System.hs b/Cabal-syntax/src/Distribution/System.hs index 7346b7f9226..62b52a20ce6 100644 --- a/Cabal-syntax/src/Distribution/System.hs +++ b/Cabal-syntax/src/Distribution/System.hs @@ -231,7 +231,7 @@ instance Pretty Platform where pretty (Platform arch os) = pretty arch <<>> Disp.char '-' <<>> pretty os instance Parsec Platform where - -- TODO: there are ambigious platforms like: `arch-word-os` + -- TODO: there are ambiguous platforms like: `arch-word-os` -- which could be parsed as -- * Platform "arch-word" "os" -- * Platform "arch" "word-os" diff --git a/Cabal-syntax/src/Distribution/Types/BuildInfo.hs b/Cabal-syntax/src/Distribution/Types/BuildInfo.hs index 17d98076106..5ebfcc471cf 100644 --- a/Cabal-syntax/src/Distribution/Types/BuildInfo.hs +++ b/Cabal-syntax/src/Distribution/Types/BuildInfo.hs @@ -52,7 +52,7 @@ data BuildInfo = BuildInfo { -- field directly. buildToolDepends :: [ExeDependency], cppOptions :: [String], -- ^ options for pre-processing Haskell code - asmOptions :: [String], -- ^ options for assmebler + asmOptions :: [String], -- ^ options for assembler cmmOptions :: [String], -- ^ options for C-- compiler ccOptions :: [String], -- ^ options for C compiler cxxOptions :: [String], -- ^ options for C++ compiler diff --git a/Cabal-syntax/src/Distribution/Types/VersionInterval.hs b/Cabal-syntax/src/Distribution/Types/VersionInterval.hs index 08accd87faa..ab2216d9345 100644 --- a/Cabal-syntax/src/Distribution/Types/VersionInterval.hs +++ b/Cabal-syntax/src/Distribution/Types/VersionInterval.hs @@ -102,7 +102,7 @@ stage1 = cataVersionRange alg where -- intersection: pairwise intersect. Strip empty intervals. Sort to restore the invariant. alg (IntersectVersionRangesF v1 v2) = mapMaybe nonEmptyInterval $ liftA2 intersectInterval (stage2and3 v1) (stage2and3 v2) --- | Creck that interval is non-empty +-- | Check that interval is non-empty nonEmptyInterval :: VersionInterval -> Maybe VersionInterval nonEmptyInterval i | nonEmptyVI i = Just i nonEmptyInterval _ = Nothing diff --git a/Cabal-syntax/src/Distribution/Types/VersionInterval/Legacy.hs b/Cabal-syntax/src/Distribution/Types/VersionInterval/Legacy.hs index 12a5e249129..202bb4db11d 100644 --- a/Cabal-syntax/src/Distribution/Types/VersionInterval/Legacy.hs +++ b/Cabal-syntax/src/Distribution/Types/VersionInterval/Legacy.hs @@ -112,7 +112,7 @@ versionIntervals (VersionIntervals is) = is type VersionInterval = (LowerBound, UpperBound) data LowerBound - = LowerBound Version !Bound -- ^ Either exlusive @(v,..@ or inclusive @[v,..@. + = LowerBound Version !Bound -- ^ Either exclusive @(v,..@ or inclusive @[v,..@. deriving (Eq, Show) data UpperBound diff --git a/Cabal-syntax/src/Distribution/Utils/Structured.hs b/Cabal-syntax/src/Distribution/Utils/Structured.hs index 165d055c274..16bc9561f49 100644 --- a/Cabal-syntax/src/Distribution/Utils/Structured.hs +++ b/Cabal-syntax/src/Distribution/Utils/Structured.hs @@ -12,7 +12,7 @@ -- -- Copyright: (c) 2019 Oleg Grenrus -- --- Structurally tag binary serialisaton stream. +-- Structurally tag binary serialisation stream. -- Useful when most 'Binary' instances are 'Generic' derived. -- -- Say you have a data type @@ -121,7 +121,7 @@ import qualified Data.Foldable type TypeName = String type ConstructorName = String --- | A sematic version of a data type. Usually 0. +-- | A semantic version of a data type. Usually 0. type TypeVersion = Word32 -- | Structure of a datatype. diff --git a/Cabal-tests/Cabal-tests.cabal b/Cabal-tests/Cabal-tests.cabal index 8e6f79465d1..a5ecaa56736 100644 --- a/Cabal-tests/Cabal-tests.cabal +++ b/Cabal-tests/Cabal-tests.cabal @@ -9,7 +9,7 @@ maintainer: cabal-devel@haskell.org homepage: http://www.haskell.org/cabal/ bug-reports: https://github.com/haskell/cabal/issues synopsis: Tests for Cabal library -description: The tests are external for development flows convinience. +description: The tests are external for development flows convenience. category: Distribution build-type: Simple diff --git a/Cabal-tests/tests/Test/Laws.hs b/Cabal-tests/tests/Test/Laws.hs index d4013fdb749..351cee7f0c6 100644 --- a/Cabal-tests/tests/Test/Laws.hs +++ b/Cabal-tests/tests/Test/Laws.hs @@ -53,7 +53,7 @@ monoid_2 :: (Eq a, Data.Monoid.Monoid a) => a -> a -> a -> Bool monoid_2 x y z = (x `mappend` y) `mappend` z == x `mappend` (y `mappend` z) --- | The 'mconcat' definition. It can be overidden for the sake of efficiency +-- | The 'mconcat' definition. It can be overridden for the sake of efficiency -- but it must still satisfy the property given by the default definition: -- -- > mconcat = foldr mappend mempty diff --git a/Cabal-tests/tests/cbits/rpmvercmp.c b/Cabal-tests/tests/cbits/rpmvercmp.c index f55764d92e3..6feda965dec 100644 --- a/Cabal-tests/tests/cbits/rpmvercmp.c +++ b/Cabal-tests/tests/cbits/rpmvercmp.c @@ -132,7 +132,7 @@ int rmpvercmp_impl(const char *a, const char *b, char *str1, char *str2) { } /* this catches the case where all numeric and alpha segments have */ - /* compared identically but the segment sepparating characters were */ + /* compared identically but the segment separating characters were */ /* different */ if ((!*one) && (!*two)) return 0; diff --git a/Cabal/src/Distribution/PackageDescription/Check.hs b/Cabal/src/Distribution/PackageDescription/Check.hs index 0a33d4ac735..13094319151 100644 --- a/Cabal/src/Distribution/PackageDescription/Check.hs +++ b/Cabal/src/Distribution/PackageDescription/Check.hs @@ -1554,7 +1554,7 @@ checkPathsModuleExtensions pd -- | Checks GHC options from all ghc-*-options fields from the given BuildInfo -- and reports flags that are OK during development process, but are --- unacceptable in a distrubuted package +-- unacceptable in a distributed package checkDevelopmentOnlyFlagsBuildInfo :: BuildInfo -> [PackageCheck] checkDevelopmentOnlyFlagsBuildInfo bi = checkDevelopmentOnlyFlagsOptions "ghc-options" (hcOptions GHC bi) diff --git a/Cabal/src/Distribution/Simple/Build/Macros.hs b/Cabal/src/Distribution/Simple/Build/Macros.hs index c0142d8845b..db0e75a8a0c 100644 --- a/Cabal/src/Distribution/Simple/Build/Macros.hs +++ b/Cabal/src/Distribution/Simple/Build/Macros.hs @@ -18,7 +18,7 @@ -- numbers. -- -- TODO Figure out what to do about backpack and internal libraries. It is very --- suspecious that this stuff works with munged package identifiers +-- suspicious that this stuff works with munged package identifiers module Distribution.Simple.Build.Macros ( generateCabalMacrosHeader, generatePackageVersionMacros, diff --git a/Cabal/src/Distribution/Simple/BuildToolDepends.hs b/Cabal/src/Distribution/Simple/BuildToolDepends.hs index 7955b0498e4..d482bfb65bc 100644 --- a/Cabal/src/Distribution/Simple/BuildToolDepends.hs +++ b/Cabal/src/Distribution/Simple/BuildToolDepends.hs @@ -16,7 +16,7 @@ import Distribution.PackageDescription -- | Desugar a "build-tools" entry into proper a executable dependency if -- possible. -- --- An entry can be so desguared in two cases: +-- An entry can be so desugared in two cases: -- -- 1. The name in build-tools matches a locally defined executable. The -- executable dependency produced is on that exe in the current package. diff --git a/Cabal/src/Distribution/Simple/Configure.hs b/Cabal/src/Distribution/Simple/Configure.hs index 8ed38a6f8df..3c43b763137 100644 --- a/Cabal/src/Distribution/Simple/Configure.hs +++ b/Cabal/src/Distribution/Simple/Configure.hs @@ -1160,7 +1160,7 @@ configureCoverage verbosity cfg comp = do computeEffectiveProfiling :: ConfigFlags -> (Bool {- lib -}, Bool {- exe -}) computeEffectiveProfiling cfg = -- The --profiling flag sets the default for both libs and exes, - -- but can be overidden by --library-profiling, or the old deprecated + -- but can be overridden by --library-profiling, or the old deprecated -- --executable-profiling flag. -- -- The --profiling-detail and --library-profiling-detail flags behave diff --git a/Cabal/src/Distribution/Simple/Utils.hs b/Cabal/src/Distribution/Simple/Utils.hs index f20b32414c0..6bf0729410a 100644 --- a/Cabal/src/Distribution/Simple/Utils.hs +++ b/Cabal/src/Distribution/Simple/Utils.hs @@ -62,7 +62,7 @@ module Distribution.Simple.Utils ( -- ** 'IOData' re-export -- -- These types are re-exported from - -- "Distribution.Utils.IOData" for convience as they're + -- "Distribution.Utils.IOData" for convenience as they're -- exposed in the API of 'rawSystemStdInOut' IOData(..), KnownIODataMode (..), diff --git a/Cabal/src/Distribution/Utils/NubList.hs b/Cabal/src/Distribution/Utils/NubList.hs index 84e6f55e051..25b8b74d648 100644 --- a/Cabal/src/Distribution/Utils/NubList.hs +++ b/Cabal/src/Distribution/Utils/NubList.hs @@ -3,7 +3,7 @@ {-# LANGUAGE ScopedTypeVariables #-} module Distribution.Utils.NubList ( NubList -- opaque - , toNubList -- smart construtor + , toNubList -- smart constructor , fromNubList , overNubList @@ -39,7 +39,7 @@ overNubList :: Ord a => ([a] -> [a]) -> NubList a -> NubList a overNubList f (NubList list) = toNubList . f $ list -- | Monoid operations on NubLists. --- For a valid Monoid instance we need to satistfy the required monoid laws; +-- For a valid Monoid instance we need to satisfy the required monoid laws; -- identity, associativity and closure. -- -- Identity : by inspection: diff --git a/Makefile b/Makefile index fb0222d9d93..8d18e756bf4 100644 --- a/Makefile +++ b/Makefile @@ -202,7 +202,7 @@ SPHINX_FLAGS:=-n -W --keep-going -E SPHINX_HTML_OUTDIR:=dist-newstyle/doc/users-guide USERGUIDE_STAMP:=$(SPHINX_HTML_OUTDIR)/index.html -# do pip install everytime so we have up to date requirements when we build +# do pip install every time so we have up to date requirements when we build users-guide: .python-sphinx-virtualenv $(USERGUIDE_STAMP) $(USERGUIDE_STAMP) : doc/*.rst mkdir -p $(SPHINX_HTML_OUTDIR) diff --git a/cabal-dev-scripts/src/GenUtils.hs b/cabal-dev-scripts/src/GenUtils.hs index c28d608a572..8029bf2fb5b 100644 --- a/cabal-dev-scripts/src/GenUtils.hs +++ b/cabal-dev-scripts/src/GenUtils.hs @@ -89,7 +89,7 @@ instance Ord OrdT where | otherwise = compare a b ------------------------------------------------------------------------------- --- Commmons +-- Commons ------------------------------------------------------------------------------- header :: String diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Dependency.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Dependency.hs index 4a7f8936537..27debc9c6f0 100644 --- a/cabal-install-solver/src/Distribution/Solver/Modular/Dependency.hs +++ b/cabal-install-solver/src/Distribution/Solver/Modular/Dependency.hs @@ -94,7 +94,7 @@ data FlaggedDep qpn = -- | Dependencies which are always enabled, for the component 'comp'. | Simple (LDep qpn) Component --- | Conversatively flatten out flagged dependencies +-- | Conservatively flatten out flagged dependencies -- -- NOTE: We do not filter out duplicates. flattenFlaggedDeps :: FlaggedDeps qpn -> [(LDep qpn, Component)] diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Linking.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Linking.hs index 1977685a7be..a348aa247b6 100644 --- a/cabal-install-solver/src/Distribution/Solver/Modular/Linking.hs +++ b/cabal-install-solver/src/Distribution/Solver/Modular/Linking.hs @@ -225,7 +225,7 @@ makeCanonical lg qpn@(Q pp _) i = -- | Link the dependencies of linked parents. -- -- When we decide to link one package against another we walk through the --- package's direct depedencies and make sure that they're all linked to each +-- package's direct dependencies and make sure that they're all linked to each -- other by merging their link groups (or creating new singleton link groups if -- they don't have link groups yet). We do not need to do this recursively, -- because having the direct dependencies in a link group means that we must diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/MessageUtils.hs b/cabal-install-solver/src/Distribution/Solver/Modular/MessageUtils.hs index 84c9005032a..684216579e8 100644 --- a/cabal-install-solver/src/Distribution/Solver/Modular/MessageUtils.hs +++ b/cabal-install-solver/src/Distribution/Solver/Modular/MessageUtils.hs @@ -30,12 +30,12 @@ allKnownExtensions = enabledExtensions ++ disabledExtensions enabledExtensions = map (prettyShow . EnableExtension) knownExtensions disabledExtensions = map (prettyShow . DisableExtension) knownExtensions --- Measure the levenshtein distance between two strings +-- Measure the Levenshtein distance between two strings distance :: String -> String -> Int distance = levenshteinDistance defaultEditCosts -- Given an `unknownElement` and a list of `elements` return the element --- from the list with the closest levenshtein distance to the `unknownElement` +-- from the list with the closest Levenshtein distance to the `unknownElement` mostSimilarElement :: String -> [String] -> String mostSimilarElement unknownElement elements = fst . minimumBy (comparing snd) . map mapDist $ elements where diff --git a/cabal-install-solver/src/Distribution/Solver/Types/PackageIndex.hs b/cabal-install-solver/src/Distribution/Solver/Types/PackageIndex.hs index 5436788a828..6106f61c3b3 100644 --- a/cabal-install-solver/src/Distribution/Solver/Types/PackageIndex.hs +++ b/cabal-install-solver/src/Distribution/Solver/Types/PackageIndex.hs @@ -171,7 +171,7 @@ mergeBuckets xs@(x:xs') ys@(y:ys') = EQ -> y : mergeBuckets xs' ys' LT -> x : mergeBuckets xs' ys --- | Override-merge oftwo indexes. +-- | Override-merge of two indexes. -- -- Packages from the second mask packages of the same exact name -- (case-sensitively) from the first. diff --git a/cabal-install-solver/tests/UnitTests/Distribution/Solver/Modular/MessageUtils.hs b/cabal-install-solver/tests/UnitTests/Distribution/Solver/Modular/MessageUtils.hs index be3cfdc9c6d..a24d5672ddd 100644 --- a/cabal-install-solver/tests/UnitTests/Distribution/Solver/Modular/MessageUtils.hs +++ b/cabal-install-solver/tests/UnitTests/Distribution/Solver/Modular/MessageUtils.hs @@ -43,7 +43,7 @@ shouldSuggestExtension = , ("NoLamdaCase", "NoLambdaCase") ] --- Given x misspelled language should suggest y langauge +-- Given x misspelled language should suggest y language shouldSuggestLanguage :: [(String, String)] shouldSuggestLanguage = [ ("GHC2020", "GHC2021") diff --git a/cabal-install/cabal-install.cabal b/cabal-install/cabal-install.cabal index eea40b9f917..cac09f97157 100644 --- a/cabal-install/cabal-install.cabal +++ b/cabal-install/cabal-install.cabal @@ -211,8 +211,8 @@ library edit-distance >= 0.2.2 && < 0.3, exceptions >= 0.10.4 && < 0.11, filepath >= 1.4.0.0 && < 1.5, - hashable >= 1.0 && < 1.4, - HTTP >= 4000.1.5 && < 4000.4, + hashable >= 1.0 && < 1.5, + HTTP >= 4000.1.5 && < 4000.5, mtl >= 2.0 && < 2.3, network-uri >= 2.6.0.2 && < 2.7, pretty >= 1.1 && < 1.2, @@ -220,7 +220,7 @@ library random >= 1.2 && < 1.3, stm >= 2.0 && < 2.6, tar >= 0.5.0.3 && < 0.6, - time >= 1.5.0.1 && < 1.11, + time >= 1.5.0.1 && < 1.12, zlib >= 0.5.3 && < 0.7, hackage-security >= 0.6.2.0 && < 0.7, text >= 1.2.3 && < 1.3, diff --git a/cabal-install/src/Distribution/Client/Check.hs b/cabal-install/src/Distribution/Client/Check.hs index a8bbdadda03..fbdf5b8cddb 100644 --- a/cabal-install/src/Distribution/Client/Check.hs +++ b/cabal-install/src/Distribution/Client/Check.hs @@ -68,7 +68,7 @@ check verbosity = do -- ghc-options: -Wall -Werror -- checkPackages will yield a warning on the last line, but it -- would not on each individual branch. - -- Hovever, this is the same way hackage does it, so we will yield + -- However, this is the same way hackage does it, so we will yield -- the exact same errors as it will. let pkg_desc = flattenPackageDescription ppd ioChecks <- checkPackageFiles verbosity pkg_desc "." diff --git a/cabal-install/src/Distribution/Client/CmdErrorMessages.hs b/cabal-install/src/Distribution/Client/CmdErrorMessages.hs index a64ed4fe6d1..ed80c474e8c 100644 --- a/cabal-install/src/Distribution/Client/CmdErrorMessages.hs +++ b/cabal-install/src/Distribution/Client/CmdErrorMessages.hs @@ -94,7 +94,7 @@ sortGroupOn key = map (\(x:|xs) -> (key x, x:xs)) ---------------------------------------------------- --- Renderering for a few project and package types +-- Rendering for a few project and package types -- renderTargetSelector :: TargetSelector -> String @@ -201,7 +201,7 @@ renderComponentKind Plural ckind = case ckind of ------------------------------------------------------- --- Renderering error messages for TargetProblem +-- Rendering error messages for TargetProblem -- -- | Default implementation of 'reportTargetProblems' simply renders one problem per line. @@ -302,7 +302,7 @@ renderTargetProblem verb _ (TargetProblemNoSuchComponent pkgid cname) = ------------------------------------------------------------ --- Renderering error messages for TargetProblemNoneEnabled +-- Rendering error messages for TargetProblemNoneEnabled -- -- | Several commands have a @TargetProblemNoneEnabled@ problem constructor. @@ -370,7 +370,7 @@ renderTargetProblemNoneEnabled verb targetSelector targets = ) ------------------------------------------------------------ --- Renderering error messages for TargetProblemNoneEnabled +-- Rendering error messages for TargetProblemNoneEnabled -- -- | Several commands have a @TargetProblemNoTargets@ problem constructor. @@ -405,7 +405,7 @@ renderTargetProblemNoTargets verb targetSelector = error $ "renderTargetProblemNoTargets: " ++ show ts ----------------------------------------------------------- --- Renderering error messages for CannotPruneDependencies +-- Rendering error messages for CannotPruneDependencies -- renderCannotPruneDependencies :: CannotPruneDependencies -> String @@ -436,7 +436,7 @@ renderCannotPruneDependencies (CannotPruneDependencies brokenPackages) = ++ " (name of library, executable, test-suite or benchmark)\n" ++ " - build Data.Foo -- module name\n" ++ " - build Data/Foo.hsc -- file name\n\n" - ++ "An ambigious target can be qualified by package, component\n" + ++ "An ambiguous target can be qualified by package, component\n" ++ "and/or component kind (lib|exe|test|bench|flib)\n" ++ " - build foo:tests -- component qualified by package\n" ++ " - build tests:Data.Foo -- module qualified by component\n" diff --git a/cabal-install/src/Distribution/Client/CmdHaddock.hs b/cabal-install/src/Distribution/Client/CmdHaddock.hs index 28450e35441..32881099073 100644 --- a/cabal-install/src/Distribution/Client/CmdHaddock.hs +++ b/cabal-install/src/Distribution/Client/CmdHaddock.hs @@ -187,12 +187,14 @@ selectComponentTarget :: SubComponentTarget selectComponentTarget = selectComponentTargetBasic reportBuildDocumentationTargetProblems :: Verbosity -> [TargetProblem'] -> IO a -reportBuildDocumentationTargetProblems verbosity problems = +reportBuildDocumentationTargetProblems verbosity problems = case problems of [TargetProblemNoneEnabled _ _] -> do - notice verbosity $ - "No documentation was generated as this package does not contain a library. " - ++ "Perhaps you want to use the --haddock-executables, --haddock-tests, --haddock-benchmarks or " - ++ "--haddock-internal flags." + notice verbosity $ unwords + [ "No documentation was generated as this package does not contain a library." + , "Perhaps you want to use the --haddock-all flag, or one or more of the" + , "--haddock-executables, --haddock-tests, --haddock-benchmarks or" + , "--haddock-internal flags." + ] System.Exit.exitSuccess _ -> reportTargetProblems verbosity "build documentation for" problems diff --git a/cabal-install/src/Distribution/Client/Compat/Semaphore.hs b/cabal-install/src/Distribution/Client/Compat/Semaphore.hs index 8ea6c3afb3a..e25442b019c 100644 --- a/cabal-install/src/Distribution/Client/Compat/Semaphore.hs +++ b/cabal-install/src/Distribution/Client/Compat/Semaphore.hs @@ -17,7 +17,7 @@ import Data.Typeable (Typeable) import Data.List.NonEmpty (NonEmpty (..)) import qualified Data.List.NonEmpty as NE --- | 'QSem' is a quantity semaphore in which the resource is aqcuired +-- | 'QSem' is a quantity semaphore in which the resource is acquired -- and released in units of one. It provides guaranteed FIFO ordering -- for satisfying blocked `waitQSem` calls. -- diff --git a/cabal-install/src/Distribution/Client/Fetch.hs b/cabal-install/src/Distribution/Client/Fetch.hs index 1f6c196c149..9dcdfb902a9 100644 --- a/cabal-install/src/Distribution/Client/Fetch.hs +++ b/cabal-install/src/Distribution/Client/Fetch.hs @@ -57,7 +57,7 @@ import Distribution.System -- * support tarball URLs via ad-hoc download cache (or in -o mode?) -- * suggest using --no-deps, unpack or fetch -o if deps cannot be satisfied -- * Port various flags from install: --- * --updage-dependencies +-- * --upgrade-dependencies -- * --constraint and --preference -- * --only-dependencies, but note it conflicts with --no-deps @@ -225,7 +225,7 @@ fetchPackage verbosity repoCtxt pkgsrc = case pkgsrc of RemoteSourceRepoPackage _repo _ -> die' verbosity $ "The 'fetch' command does not yet support remote " - ++ "source repositores." + ++ "source repositories." RepoTarballPackage repo pkgid _ -> do _ <- fetchRepoTarball verbosity repoCtxt repo pkgid diff --git a/cabal-install/src/Distribution/Client/HashValue.hs b/cabal-install/src/Distribution/Client/HashValue.hs index abde9c909a9..67117b231cc 100644 --- a/cabal-install/src/Distribution/Client/HashValue.hs +++ b/cabal-install/src/Distribution/Client/HashValue.hs @@ -64,7 +64,7 @@ readFileHashValue tarball = -- | Convert a hash from TUF metadata into a 'PackageSourceHash'. -- --- Note that TUF hashes don't neessarily have to be SHA256, since it can +-- Note that TUF hashes don't necessarily have to be SHA256, since it can -- support new algorithms in future. -- hashFromTUF :: Sec.Hash -> HashValue diff --git a/cabal-install/src/Distribution/Client/ProjectConfig.hs b/cabal-install/src/Distribution/Client/ProjectConfig.hs index 9ca62bd63e7..0883e4cea74 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig.hs @@ -1259,7 +1259,7 @@ data CabalFileParseError = CabalFileParseError [PWarning] -- ^ warnings deriving (Typeable) --- | Manual instance which skips file contentes +-- | Manual instance which skips file contents instance Show CabalFileParseError where showsPrec d (CabalFileParseError fp _ es mv ws) = showParen (d > 10) $ showString "CabalFileParseError" diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning.hs b/cabal-install/src/Distribution/Client/ProjectPlanning.hs index 7d4ec4186f7..2e447c2cdff 100644 --- a/cabal-install/src/Distribution/Client/ProjectPlanning.hs +++ b/cabal-install/src/Distribution/Client/ProjectPlanning.hs @@ -624,7 +624,7 @@ rebuildInstallPlan verbosity Map.fromList [ (pkgname, stanzas) | pkg <- localPackages - -- TODO: misnormer: we should separate + -- TODO: misnomer: we should separate -- builtin/global/inplace/local packages -- and packages explicitly mentioned in the project -- @@ -2756,7 +2756,7 @@ pruneInstallPlanToTargets targetActionType perPkgTargetsMap elaboratedPlan = -- | This is a temporary data type, where we temporarily -- override the graph dependencies of an 'ElaboratedPackage', -- so we can take a closure over them. We'll throw out the --- overriden dependencies when we're done so it's strictly temporary. +-- overridden dependencies when we're done so it's strictly temporary. -- -- For 'ElaboratedComponent', this the cached unit IDs always -- coincide with the real thing. @@ -3203,7 +3203,7 @@ packageSetupScriptStyle pkg -- Note that adding default deps means these deps are actually /added/ to the -- packages that we get out of the solver in the 'SolverInstallPlan'. Making -- implicit setup deps explicit is a problem in the post-solver stages because --- we still need to distinguish the case of explicit and implict setup deps. +-- we still need to distinguish the case of explicit and implicit setup deps. -- See 'rememberImplicitSetupDeps'. -- -- Note in addition to adding default setup deps, we also use diff --git a/cabal-install/src/Distribution/Client/RebuildMonad.hs b/cabal-install/src/Distribution/Client/RebuildMonad.hs index 3818aced7a3..f7b169f418f 100644 --- a/cabal-install/src/Distribution/Client/RebuildMonad.hs +++ b/cabal-install/src/Distribution/Client/RebuildMonad.hs @@ -79,7 +79,7 @@ import System.Directory newtype Rebuild a = Rebuild (ReaderT FilePath (StateT [MonitorFilePath] IO) a) deriving (Functor, Applicative, Monad, MonadIO) --- | Use this wihin the body action of 'rerunIfChanged' to declare that the +-- | Use this within the body action of 'rerunIfChanged' to declare that the -- action depends on the given files. This can be based on what the action -- actually did. It is these files that will be checked for changes next -- time 'rerunIfChanged' is called for that 'FileMonitor'. diff --git a/cabal-install/src/Distribution/Client/Setup.hs b/cabal-install/src/Distribution/Client/Setup.hs index c53333ba397..a132b01d528 100644 --- a/cabal-install/src/Distribution/Client/Setup.hs +++ b/cabal-install/src/Distribution/Client/Setup.hs @@ -1453,7 +1453,7 @@ listOptions = listSimpleOutput (\v flags -> flags { listSimpleOutput = v }) trueArg , option ['i'] ["ignore-case"] - "Ignore case destictions" + "Ignore case distinctions" listCaseInsensitive (\v flags -> flags { listCaseInsensitive = v }) (boolOpt' (['i'], ["ignore-case"]) (['I'], ["strict-case"])) diff --git a/cabal-install/src/Distribution/Client/SrcDist.hs b/cabal-install/src/Distribution/Client/SrcDist.hs index 95814d9a84a..b418733c645 100644 --- a/cabal-install/src/Distribution/Client/SrcDist.hs +++ b/cabal-install/src/Distribution/Client/SrcDist.hs @@ -1,5 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} --- | Utilities to implemenet cabal @v2-sdist@. +-- | Utilities to implement cabal @v2-sdist@. module Distribution.Client.SrcDist ( allPackageSourceFiles, packageDirToSdist, diff --git a/cabal-install/src/Distribution/Client/TargetSelector.hs b/cabal-install/src/Distribution/Client/TargetSelector.hs index 39efafd6b3a..80d65955dd2 100644 --- a/cabal-install/src/Distribution/Client/TargetSelector.hs +++ b/cabal-install/src/Distribution/Client/TargetSelector.hs @@ -204,7 +204,7 @@ instance Structured SubComponentTarget readTargetSelectors :: [PackageSpecifier (SourcePackage (PackageLocation a))] -> Maybe ComponentKindFilter -- ^ This parameter is used when there are ambiguous selectors. - -- If it is 'Just', then we attempt to resolve ambiguitiy + -- If it is 'Just', then we attempt to resolve ambiguity -- by applying it, since otherwise there is no way to allow -- contextually valid yet syntactically ambiguous selectors. -- (#4676, #5461) diff --git a/cabal-install/src/Distribution/Client/Types/Repo.hs b/cabal-install/src/Distribution/Client/Types/Repo.hs index 2a03440e23e..7804c1f3c5f 100644 --- a/cabal-install/src/Distribution/Client/Types/Repo.hs +++ b/cabal-install/src/Distribution/Client/Types/Repo.hs @@ -71,7 +71,7 @@ instance Pretty RemoteRepo where pretty (remoteRepoName r) <<>> Disp.colon <<>> Disp.text (uriToString id (remoteRepoURI r) []) --- | Note: serialised format represends 'RemoteRepo' only partially. +-- | Note: serialised format represents 'RemoteRepo' only partially. instance Parsec RemoteRepo where parsec = do name <- parsec @@ -150,7 +150,7 @@ data Repo , repoLocalDir :: FilePath } - -- | Standard (unsecured) remote repositores + -- | Standard (unsecured) remote repositories | RepoRemote { repoRemote :: RemoteRepo , repoLocalDir :: FilePath diff --git a/cabal-install/tests/UnitTests/Distribution/Client/VCS.hs b/cabal-install/tests/UnitTests/Distribution/Client/VCS.hs index 160076e94a6..84bf78983d0 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/VCS.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/VCS.hs @@ -39,7 +39,7 @@ import UnitTests.TempTestDir (withTestDir, removeDirectoryRecursiveHack) -- working state. -- -- The first test simply checks that the test infrastructure works. It --- constructs a repository on disk and then checks out every tag or commmit +-- constructs a repository on disk and then checks out every tag or commit -- and checks that the working state is the same as the pure representation. -- -- The second test works in a similar way but tests 'syncSourceRepos'. It diff --git a/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs b/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs index 33e8b41a7d3..d46f1804ad1 100644 --- a/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs +++ b/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs @@ -1572,7 +1572,7 @@ db23 = [ -- or also its link target. -- -- It turns out that as long as the Single Instance Restriction is in place, --- it does not matter, because there will aways be an option that is failing +-- it does not matter, because there will always be an option that is failing -- due to the SIR, which contains the link target in its conflict set. -- -- Even if the SIR is not in place, if there is a solution, one will always diff --git a/cabal-testsuite/PackageTests/CCompilerOverride/setup.test.hs b/cabal-testsuite/PackageTests/CCompilerOverride/setup.test.hs index 621d9cace8b..7c01bcef821 100644 --- a/cabal-testsuite/PackageTests/CCompilerOverride/setup.test.hs +++ b/cabal-testsuite/PackageTests/CCompilerOverride/setup.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude --- Test that all the respective defines -DNOERROR... specified in variosu ways +-- Test that all the respective defines -DNOERROR... specified in various ways -- all end up routed to the C compiler. Otherwise the C file we depend on will -- not compile. main = setupAndCabalTest $ do diff --git a/cabal-testsuite/PackageTests/DeterministicAr/setup-default-ar.test.hs b/cabal-testsuite/PackageTests/DeterministicAr/setup-default-ar.test.hs index e446d153d8d..fc59fd54e51 100644 --- a/cabal-testsuite/PackageTests/DeterministicAr/setup-default-ar.test.hs +++ b/cabal-testsuite/PackageTests/DeterministicAr/setup-default-ar.test.hs @@ -5,7 +5,7 @@ import Control.Monad.IO.Class import Test.Cabal.CheckArMetadata --- Test that setup determinstically generates object archives +-- Test that setup deterministically generates object archives main = setupAndCabalTest $ do setup_build [] dist_dir <- fmap testDistDir getTestEnv diff --git a/cabal-testsuite/PackageTests/DeterministicAr/setup-old-ar-without-at-args.test.hs b/cabal-testsuite/PackageTests/DeterministicAr/setup-old-ar-without-at-args.test.hs index 56e9c5b8d10..0d18b42dcf9 100644 --- a/cabal-testsuite/PackageTests/DeterministicAr/setup-old-ar-without-at-args.test.hs +++ b/cabal-testsuite/PackageTests/DeterministicAr/setup-old-ar-without-at-args.test.hs @@ -5,7 +5,7 @@ import Control.Monad.IO.Class import Test.Cabal.CheckArMetadata --- Test that setup determinstically generates object archives +-- Test that setup deterministically generates object archives main = setupAndCabalTest $ do setup_build ["--disable-response-files"] dist_dir <- fmap testDistDir getTestEnv diff --git a/cabal-testsuite/PackageTests/HaddockWarn/cabal.out b/cabal-testsuite/PackageTests/HaddockWarn/cabal.out index ab3365aeea6..fae3d5423de 100644 --- a/cabal-testsuite/PackageTests/HaddockWarn/cabal.out +++ b/cabal-testsuite/PackageTests/HaddockWarn/cabal.out @@ -1,3 +1,3 @@ # cabal v2-haddock Resolving dependencies... -No documentation was generated as this package does not contain a library. Perhaps you want to use the --haddock-executables, --haddock-tests, --haddock-benchmarks or --haddock-internal flags. \ No newline at end of file +No documentation was generated as this package does not contain a library. Perhaps you want to use the --haddock-all flag, or one or more of the --haddock-executables, --haddock-tests, --haddock-benchmarks or --haddock-internal flags. \ No newline at end of file diff --git a/cabal-testsuite/PackageTests/Regression/T5309/T5309.cabal b/cabal-testsuite/PackageTests/Regression/T5309/T5309.cabal index a19f4360c34..4f2ec422696 100644 --- a/cabal-testsuite/PackageTests/Regression/T5309/T5309.cabal +++ b/cabal-testsuite/PackageTests/Regression/T5309/T5309.cabal @@ -37,7 +37,7 @@ common ffi-build-info -- to locate when preprocessing the C files. Without listing the directories containing -- the C header files here, the FFI preprocession (hsc2hs, c2hs,etc.) will fail to locate -- the requisite files. - -- Note also, that the parent directory of the nessicary C header files must be specified. + -- Note also, that the parent directory of the necessary C header files must be specified. -- The preprocesser will not recursively look in subdirectories for C header files! include-dirs: memoized-tcm diff --git a/cabal-testsuite/PackageTests/Regression/T5309/lib/Data/TCM/Memoized/FFI.hsc b/cabal-testsuite/PackageTests/Regression/T5309/lib/Data/TCM/Memoized/FFI.hsc index 2a96ba7851d..b900d612c04 100644 --- a/cabal-testsuite/PackageTests/Regression/T5309/lib/Data/TCM/Memoized/FFI.hsc +++ b/cabal-testsuite/PackageTests/Regression/T5309/lib/Data/TCM/Memoized/FFI.hsc @@ -2,7 +2,7 @@ -- | -- TODO: Document module. -- --- Exports C types for dynamic characters and their constructors allong with +-- Exports C types for dynamic characters and their constructors along with -- an FFI binding for the memoizing TCM structure. ----------------------------------------------------------------------------- @@ -40,7 +40,7 @@ import System.IO.Unsafe -- | --- A convient type alias for improved clairity of use. +-- A convenient type alias for improved clarity of use. type CBufferUnit = CULong -- This will be compatible with uint64_t @@ -267,7 +267,7 @@ constructElementFromExportable exChar = do -- /O(1)/ -- -- Malloc and populate a pointer to a C representation of a dynamic character. --- The buffer of the resulting value is intentially zeroed out. +-- The buffer of the resulting value is intentionally zeroed out. constructEmptyElement :: Int -- ^ Bit width of a dynamic character element. -> IO (Ptr DCElement) constructEmptyElement alphabetSize = do diff --git a/cabal-testsuite/cabal-testsuite.cabal b/cabal-testsuite/cabal-testsuite.cabal index f4a4a5638ff..7a93a7ebe6c 100644 --- a/cabal-testsuite/cabal-testsuite.cabal +++ b/cabal-testsuite/cabal-testsuite.cabal @@ -90,7 +90,7 @@ executable cabal-tests ghc-options: -threaded build-depends: , cabal-testsuite - -- cosntraints inherited via lib:cabal-testsuite component + -- constraints inherited via lib:cabal-testsuite component , async , exceptions , filepath diff --git a/doc/cabal-project.rst b/doc/cabal-project.rst index 0a6e4aa4672..c9b7c3bd309 100644 --- a/doc/cabal-project.rst +++ b/doc/cabal-project.rst @@ -613,7 +613,7 @@ The following settings control the behavior of the dependency solver: overriding repository. The special repository reference :rest stands for "all the other repositories" - and can be useful to avoid lenghty lists of repository names: + and can be useful to avoid lengthy lists of repository names: :: diff --git a/doc/developing-packages.rst b/doc/developing-packages.rst index 236217a68a4..135b67145ca 100644 --- a/doc/developing-packages.rst +++ b/doc/developing-packages.rst @@ -276,7 +276,7 @@ If the package contains an executable, you can run it with: $ cabal run -and the executable can also be installed for convenince: +and the executable can also be installed for convenience: .. code-block:: console diff --git a/doc/file-format-changelog.rst b/doc/file-format-changelog.rst index 78afa510ae6..b1e1af2ce31 100644 --- a/doc/file-format-changelog.rst +++ b/doc/file-format-changelog.rst @@ -26,9 +26,9 @@ relative to the respective preceding *published* version. enumerates executabes (possibly brought into scope by :pkg-field:`build-tool-depends`) that are run after all other preprocessors. These executables are invoked with a target dir for output, a sequence of all source directories with source files of - local lib components that the given test stanza dependens on, and + local lib components that the given test stanza depends on, and following a double dash, all options cabal would pass to ghc for a - build. They are expected to output a newline-seperated list of + build. They are expected to output a newline-separated list of generated modules which have been written to the targetdir. This can be used for driving doctests and other discover-style tests generated from source code. @@ -169,7 +169,7 @@ relative to the respective preceding *published* version. * New :pkg-field:`library:virtual-modules` field added. * New :pkg-field:`cxx-sources` and :pkg-field:`cxx-options` fields - added for suppporting bundled foreign routines implemented in C++. + added for supporting bundled foreign routines implemented in C++. * New :pkg-field:`extra-bundled-libraries` field for specifying additional custom library objects to be installed. diff --git a/doc/getting-started.rst b/doc/getting-started.rst index b8151d20061..f1a64d6b0c0 100644 --- a/doc/getting-started.rst +++ b/doc/getting-started.rst @@ -27,13 +27,13 @@ unix shells and PowerShell (if you're on Windows). $ cabal init myfirstapp -n .. note:: ``myfirstapp`` stands for the directory (or path) where the project - will reside in, if ommited, ``cabal init`` will do its proceedings + will reside in, if omitted, ``cabal init`` will do its proceedings in the directory it's called in. .. note:: ``-n`` stands for ``--non-interactive``, which means that cabal will try to guess how to set up the project for you and use the default settings, which will serve us well for the purpose of this tutorial. - When setting up your projects in the future, you will likely want to ommit ``-n`` + When setting up your projects in the future, you will likely want to omit ``-n`` and do just ``cabal init``, so that cabal will interactively ask you for the details on how the project should be set up (while still offering reasonable defaults on every step). diff --git a/editors/vim/example.cabal b/editors/vim/example.cabal index 7f505ad5055..4c3554bcdc9 100644 --- a/editors/vim/example.cabal +++ b/editors/vim/example.cabal @@ -12,7 +12,7 @@ build-type: Simple description: description: Trying to fool highlighter, successfully? Description is long and often written on multiple lines Haskell2010 - type subdir extensions:, the colon could fool highligher + type subdir extensions:, the colon could fool highlighter DeriveFunctor as if else elif should not be matched here tested-with: diff --git a/stack.yaml b/stack.yaml index 7954208b9a1..3e31c03175c 100644 --- a/stack.yaml +++ b/stack.yaml @@ -18,7 +18,7 @@ extra-deps: - rere-0.2@rev:1 # We require the released version of Cabal and Cabal-syntax for cabal-testsuite -# but ususally we have a development, newer version set in the local package +# but usually we have a development, newer version set in the local package # Also needed for hackage-security and Win32 allow-newer: true diff --git a/validate.sh b/validate.sh index f3636c63969..0b227c9f6bd 100755 --- a/validate.sh +++ b/validate.sh @@ -58,7 +58,7 @@ Available options: --partial-hackage-tests Run hackage-tests on parts of Hackage data -v, --verbose Verbose output -q, --quiet Less output - -s, --step STEP Run only specific step (can be specified mutliple times) + -s, --step STEP Run only specific step (can be specified multiple times) --list-steps List steps and build-targets and exit --help Print this message and exit EOF