summaryrefslogtreecommitdiff
path: root/libraries
diff options
context:
space:
mode:
Diffstat (limited to 'libraries')
-rw-r--r--libraries/base/Data/Semigroup/Internal.hs2
-rw-r--r--libraries/base/GHC/ExecutionStack/Internal.hsc2
-rw-r--r--libraries/base/GHC/IO/Encoding.hs4
-rw-r--r--libraries/base/GHC/IO/Encoding/CodePage/API.hs2
-rw-r--r--libraries/base/GHC/IO/Handle/Internals.hs2
-rw-r--r--libraries/base/GHC/IO/Handle/Lock.hs2
-rw-r--r--libraries/base/GHC/IO/Handle/Types.hs2
-rw-r--r--libraries/base/GHC/List.hs2
-rw-r--r--libraries/base/GHC/StaticPtr.hs2
-rw-r--r--libraries/base/GHC/TypeNats.hs2
-rw-r--r--libraries/base/System/IO.hs2
-rw-r--r--libraries/base/changelog.md2
-rw-r--r--libraries/base/codepages/MakeTable.hs2
-rw-r--r--libraries/base/configure.ac2
-rw-r--r--libraries/base/tests/IO/all.T2
-rw-r--r--libraries/ghc-prim/cbits/ctz.c2
-rw-r--r--libraries/integer-gmp/src/GHC/Integer/Type.hs2
-rw-r--r--libraries/template-haskell/Language/Haskell/TH/Syntax.hs2
18 files changed, 19 insertions, 19 deletions
diff --git a/libraries/base/Data/Semigroup/Internal.hs b/libraries/base/Data/Semigroup/Internal.hs
index 4f75afccb5..4ce73d0c05 100644
--- a/libraries/base/Data/Semigroup/Internal.hs
+++ b/libraries/base/Data/Semigroup/Internal.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
--- | Auxilary definitions for 'Semigroup'
+-- | Auxiliary definitions for 'Semigroup'
--
-- This module provides some @newtype@ wrappers and helpers which are
-- reexported from the "Data.Semigroup" module or imported directly
diff --git a/libraries/base/GHC/ExecutionStack/Internal.hsc b/libraries/base/GHC/ExecutionStack/Internal.hsc
index 9f9e979af9..7db1e86ff7 100644
--- a/libraries/base/GHC/ExecutionStack/Internal.hsc
+++ b/libraries/base/GHC/ExecutionStack/Internal.hsc
@@ -150,7 +150,7 @@ stackFrames st@(StackTrace fptr) = unsafePerformIO $ withSession $ \sess -> do
unknown symbols). I think this is a reasonable price to pay, however, as
module loading/unloading is a rather rare event.
- Morover, we stand to gain a great deal by lazy lookups as the stack frames
+ Moreover, we stand to gain a great deal by lazy lookups as the stack frames
may never even be requested, meaning the only effort wasted is the
collection of the stack frames themselves.
diff --git a/libraries/base/GHC/IO/Encoding.hs b/libraries/base/GHC/IO/Encoding.hs
index 735c1b0a37..d607b7e7b5 100644
--- a/libraries/base/GHC/IO/Encoding.hs
+++ b/libraries/base/GHC/IO/Encoding.hs
@@ -82,7 +82,7 @@ utf8_bom = UTF8.utf8_bom
utf16 :: TextEncoding
utf16 = UTF16.utf16
--- | The UTF-16 Unicode encoding (litte-endian)
+-- | The UTF-16 Unicode encoding (little-endian)
utf16le :: TextEncoding
utf16le = UTF16.utf16le
@@ -95,7 +95,7 @@ utf16be = UTF16.utf16be
utf32 :: TextEncoding
utf32 = UTF32.utf32
--- | The UTF-32 Unicode encoding (litte-endian)
+-- | The UTF-32 Unicode encoding (little-endian)
utf32le :: TextEncoding
utf32le = UTF32.utf32le
diff --git a/libraries/base/GHC/IO/Encoding/CodePage/API.hs b/libraries/base/GHC/IO/Encoding/CodePage/API.hs
index 65a1b377db..9c2dc0e85c 100644
--- a/libraries/base/GHC/IO/Encoding/CodePage/API.hs
+++ b/libraries/base/GHC/IO/Encoding/CodePage/API.hs
@@ -317,7 +317,7 @@ cpEncode cp _max_char_size = \ibuf obuf -> do
| ocnt == 0 = return (Left True)
| otherwise = alloca $ \defaulted_ptr -> do
poke defaulted_ptr False
- err <- c_WideCharToMultiByte (fromIntegral cp) 0 -- NB: the WC_ERR_INVALID_CHARS flag is uselses: only has an effect with the UTF-8 code page
+ err <- c_WideCharToMultiByte (fromIntegral cp) 0 -- NB: the WC_ERR_INVALID_CHARS flag is useless: only has an effect with the UTF-8 code page
iptr (fromIntegral icnt) optr (fromIntegral ocnt)
nullPtr defaulted_ptr
defaulted <- peek defaulted_ptr
diff --git a/libraries/base/GHC/IO/Handle/Internals.hs b/libraries/base/GHC/IO/Handle/Internals.hs
index 5f767348ee..21284a776c 100644
--- a/libraries/base/GHC/IO/Handle/Internals.hs
+++ b/libraries/base/GHC/IO/Handle/Internals.hs
@@ -358,7 +358,7 @@ ioe_bufsiz n = ioException
-- Wrapper for Handle encoding/decoding.
-- The interface for TextEncoding changed so that a TextEncoding doesn't raise
--- an exception if it encounters an invalid sequnce. Furthermore, encoding
+-- an exception if it encounters an invalid sequence. Furthermore, encoding
-- returns a reason as to why encoding stopped, letting us know if it was due
-- to input/output underflow or an invalid sequence.
--
diff --git a/libraries/base/GHC/IO/Handle/Lock.hs b/libraries/base/GHC/IO/Handle/Lock.hs
index 09df4a24ae..6d8938c35d 100644
--- a/libraries/base/GHC/IO/Handle/Lock.hs
+++ b/libraries/base/GHC/IO/Handle/Lock.hs
@@ -44,7 +44,7 @@ import GHC.IO.Handle.Lock.NoOp
-- 2) The implementation uses 'LockFileEx' on Windows and 'flock' otherwise,
-- hence all of their caveats also apply here.
--
--- 3) On non-Windows plaftorms that don't support 'flock' (e.g. Solaris) this
+-- 3) On non-Windows platforms that don't support 'flock' (e.g. Solaris) this
-- function throws 'FileLockingNotImplemented'. We deliberately choose to not
-- provide fcntl based locking instead because of its broken semantics.
--
diff --git a/libraries/base/GHC/IO/Handle/Types.hs b/libraries/base/GHC/IO/Handle/Types.hs
index aeb72af847..6923d252b9 100644
--- a/libraries/base/GHC/IO/Handle/Types.hs
+++ b/libraries/base/GHC/IO/Handle/Types.hs
@@ -386,7 +386,7 @@ nativeNewline = LF
#endif
-- | Map @\'\\r\\n\'@ into @\'\\n\'@ on input, and @\'\\n\'@ to the native newline
--- represetnation on output. This mode can be used on any platform, and
+-- representation on output. This mode can be used on any platform, and
-- works with text files using any newline convention. The downside is
-- that @readFile >>= writeFile@ might yield a different file.
--
diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs
index 65fa4f54a5..ba5229f9cb 100644
--- a/libraries/base/GHC/List.hs
+++ b/libraries/base/GHC/List.hs
@@ -425,7 +425,7 @@ The type of (g :: (a -> b -> b) -> b -> b) allows us to apply parametricity:
Either the tuple is returned (trivial), or scanrFB is called:
g (scanrFB f c) (q0,n) = scanrFB ... (g' (scanrFB f c) (q0,n))
Notice that thanks to the strictness of scanrFB, the expression
-g' (scanrFB f c) (q0,n) gets evaluated aswell. In particular, if g' is a
+g' (scanrFB f c) (q0,n) gets evaluated as well. In particular, if g' is a
recursive case of g, parametricity applies again and we will again have a
possible call to scanrFB. In short, g (scanrFB f c) (q0,n) will end up being
completely evaluated. This is resource consuming for large lists and if the
diff --git a/libraries/base/GHC/StaticPtr.hs b/libraries/base/GHC/StaticPtr.hs
index b8d5c116d1..dcffbad701 100644
--- a/libraries/base/GHC/StaticPtr.hs
+++ b/libraries/base/GHC/StaticPtr.hs
@@ -103,7 +103,7 @@ class IsStatic p where
instance IsStatic StaticPtr where
fromStaticPtr = id
--- | Miscelaneous information available for debugging purposes.
+-- | Miscellaneous information available for debugging purposes.
data StaticPtrInfo = StaticPtrInfo
{ -- | Package key of the package where the static pointer is defined
spInfoUnitId :: String
diff --git a/libraries/base/GHC/TypeNats.hs b/libraries/base/GHC/TypeNats.hs
index da06627118..aba47b0b96 100644
--- a/libraries/base/GHC/TypeNats.hs
+++ b/libraries/base/GHC/TypeNats.hs
@@ -113,7 +113,7 @@ After inlining and simplification, this ends up looking something like this:
`KnownNat` is the constructor for dictionaries for the class `KnownNat`.
See Note [magicDictId magic] in "basicType/MkId.hs" for details on how
-we actually construct the dictionry.
+we actually construct the dictionary.
Note that using `Any Nat` is not really correct, as multilple calls to
`someNatVal` would violate coherence:
diff --git a/libraries/base/System/IO.hs b/libraries/base/System/IO.hs
index 4549c8f12e..2ae0e1e6da 100644
--- a/libraries/base/System/IO.hs
+++ b/libraries/base/System/IO.hs
@@ -202,7 +202,7 @@ module System.IO (
-- as @\'\\r\\n\'@.
--
-- A text-mode 'Handle' has an associated 'NewlineMode' that
- -- specifies how to transate newline characters. The
+ -- specifies how to translate newline characters. The
-- 'NewlineMode' specifies the input and output translation
-- separately, so that for instance you can translate @\'\\r\\n\'@
-- to @\'\\n\'@ on input, but leave newlines as @\'\\n\'@ on output.
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index fa0d2d4e95..026de1df82 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -295,7 +295,7 @@
in constant space when applied to lists. (#10830)
* `mkFunTy`, `mkAppTy`, and `mkTyConApp` from `Data.Typeable` no longer exist.
- This functionality is superceded by the interfaces provided by
+ This functionality is superseded by the interfaces provided by
`Type.Reflection`.
* `mkTyCon3` is no longer exported by `Data.Typeable`. This function is
diff --git a/libraries/base/codepages/MakeTable.hs b/libraries/base/codepages/MakeTable.hs
index b276e4b1a0..0806e268eb 100644
--- a/libraries/base/codepages/MakeTable.hs
+++ b/libraries/base/codepages/MakeTable.hs
@@ -138,7 +138,7 @@ mkConvArray xs = "ConvArray \"" ++ concatMap mkHex xs ++ "\"#"
--
-- Fix a block size S which is a power of two. We compress an array of N
-- entries (where N>>S) as follows. First, split the array into blocks of size
--- S, then remove all repeate blocks to form the "value" array. Then construct
+-- S, then remove all repeated blocks to form the "value" array. Then construct
-- a separate "index" array which maps the position of blocks in the old array
-- to a position in the value array.
--
diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac
index d34224acc7..eff986fb96 100644
--- a/libraries/base/configure.ac
+++ b/libraries/base/configure.ac
@@ -37,7 +37,7 @@ AC_CHECK_HEADERS([ctype.h errno.h fcntl.h inttypes.h limits.h signal.h sys/file.
AC_SYS_LARGEFILE
dnl ** check for wide-char classifications
-dnl FreeBSD has an emtpy wctype.h, so test one of the affected
+dnl FreeBSD has an empty wctype.h, so test one of the affected
dnl functions if it's really there.
AC_CHECK_HEADERS([wctype.h], [AC_CHECK_FUNCS(iswspace)])
diff --git a/libraries/base/tests/IO/all.T b/libraries/base/tests/IO/all.T
index 189fbebb88..818ce67267 100644
--- a/libraries/base/tests/IO/all.T
+++ b/libraries/base/tests/IO/all.T
@@ -138,7 +138,7 @@ test('T17414',
when(opsys('mingw32'), fragile(17453)),
# It is common for tmpfs to be mounted to a small tmpfs on modern Linux
# distributions. This test needs to create a large file which will exceed the
- # size of this filesystem onsequently we must skip it (see #17459).
+ # size of this filesystem consequently we must skip it (see #17459).
when(opsys('linux'), skip),
high_memory_usage],
compile_and_run, [''])
diff --git a/libraries/ghc-prim/cbits/ctz.c b/libraries/ghc-prim/cbits/ctz.c
index fc98716968..755ad6e0b3 100644
--- a/libraries/ghc-prim/cbits/ctz.c
+++ b/libraries/ghc-prim/cbits/ctz.c
@@ -32,7 +32,7 @@ StgWord
hs_ctz64(StgWord64 x)
{
#if defined(__GNUC__) && (defined(i386_HOST_ARCH) || defined(powerpc_HOST_ARCH))
- /* On Linux/i386, the 64bit `__builtin_ctzll()` instrinsic doesn't
+ /* On Linux/i386, the 64bit `__builtin_ctzll()` intrinsic doesn't
get inlined by GCC but rather a short `__ctzdi2` runtime function
is inserted when needed into compiled object files.
diff --git a/libraries/integer-gmp/src/GHC/Integer/Type.hs b/libraries/integer-gmp/src/GHC/Integer/Type.hs
index 1b7d6cafba..44a2964895 100644
--- a/libraries/integer-gmp/src/GHC/Integer/Type.hs
+++ b/libraries/integer-gmp/src/GHC/Integer/Type.hs
@@ -1852,7 +1852,7 @@ unsafeSnocFreezeBigNat# mbn0@(MBN# mba0#) limb# s = go s'
_ <- svoid (writeWordArray# mba# n# limb#)
unsafeFreezeBigNat# (MBN# mba#)
--- | May shrink underlyng 'ByteArray#' if needed to satisfy BigNat invariant
+-- | May shrink underlying 'ByteArray#' if needed to satisfy BigNat invariant
unsafeRenormFreezeBigNat# :: MutBigNat s -> S s BigNat
unsafeRenormFreezeBigNat# mbn s
| isTrue# (n0# ==# 0#) = (# s'', nullBigNat #)
diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
index 81cd588ec8..fb9556db54 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
@@ -1724,7 +1724,7 @@ type Arity = Int
-- | In 'PrimTyConI', is the type constructor unlifted?
type Unlifted = Bool
--- | 'InstanceDec' desribes a single instance of a class or type function.
+-- | 'InstanceDec' describes a single instance of a class or type function.
-- It is just a 'Dec', but guaranteed to be one of the following:
--
-- * 'InstanceD' (with empty @['Dec']@)