summaryrefslogtreecommitdiff
path: root/libraries/base
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base')
-rw-r--r--libraries/base/Data/Data.hs2
-rw-r--r--libraries/base/Data/IORef.hs2
-rw-r--r--libraries/base/Data/Maybe.hs2
-rw-r--r--libraries/base/Data/STRef.hs2
-rw-r--r--libraries/base/Foreign/Marshal/Utils.hs32
-rw-r--r--libraries/base/GHC/Event/Thread.hs4
-rw-r--r--libraries/base/GHC/IO/Handle/Lock/LinuxOFD.hsc4
-rw-r--r--libraries/base/GHC/Int.hs32
-rw-r--r--libraries/base/GHC/List.hs4
-rw-r--r--libraries/base/GHC/Read.hs2
-rw-r--r--libraries/base/System/CPUTime.hsc2
-rw-r--r--libraries/base/System/Environment/ExecutablePath.hsc1
-rw-r--r--libraries/base/System/IO/Error.hs6
-rw-r--r--libraries/base/tests/IO/T2122.hs2
14 files changed, 54 insertions, 43 deletions
diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs
index 8e285ac07c..a8dfa61115 100644
--- a/libraries/base/Data/Data.hs
+++ b/libraries/base/Data/Data.hs
@@ -194,7 +194,7 @@ immediate subterms. In the definition of gmapQr, extra effort is
needed. We use a higher-order accumulation trick to mediate between
left-associative constructor application vs. right-associative binary
operation (e.g., @(:)@). When the query is meant to compute a value
-of type @r@, then the result type withing generic folding is @r -> r@.
+of type @r@, then the result type within generic folding is @r -> r@.
So the result of folding is a function to which we finally pass the
right unit.
diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs
index 44769268cf..2886e594d3 100644
--- a/libraries/base/Data/IORef.hs
+++ b/libraries/base/Data/IORef.hs
@@ -49,7 +49,7 @@ mkWeakIORef r@(IORef (STRef r#)) (IO finalizer) = IO $ \s ->
-- |Mutate the contents of an 'IORef'.
--
-- Be warned that 'modifyIORef' does not apply the function strictly. This
--- means if the program calls 'modifyIORef' many times, but seldomly uses the
+-- means if the program calls 'modifyIORef' many times, but seldom uses the
-- value, thunks will pile up in memory resulting in a space leak. This is a
-- common mistake made when using an IORef as a counter. For example, the
-- following will likely produce a stack overflow:
diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs
index 2bd0b1e00e..f646faeb9a 100644
--- a/libraries/base/Data/Maybe.hs
+++ b/libraries/base/Data/Maybe.hs
@@ -148,7 +148,7 @@ fromJust :: HasCallStack => Maybe a -> a
fromJust Nothing = error "Maybe.fromJust: Nothing" -- yuck
fromJust (Just x) = x
--- | The 'fromMaybe' function takes a default value and and 'Maybe'
+-- | The 'fromMaybe' function takes a default value and a 'Maybe'
-- value. If the 'Maybe' is 'Nothing', it returns the default values;
-- otherwise, it returns the value contained in the 'Maybe'.
--
diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs
index 5b8c6b7901..3636e6a8a6 100644
--- a/libraries/base/Data/STRef.hs
+++ b/libraries/base/Data/STRef.hs
@@ -40,7 +40,7 @@ import GHC.STRef
-- "Hello, world!"
--
-- Be warned that 'modifySTRef' does not apply the function strictly. This
--- means if the program calls 'modifySTRef' many times, but seldomly uses the
+-- means if the program calls 'modifySTRef' many times, but seldom uses the
-- value, thunks will pile up in memory resulting in a space leak. This is a
-- common mistake made when using an 'STRef' as a counter. For example, the
-- following will leak memory and may produce a stack overflow:
diff --git a/libraries/base/Foreign/Marshal/Utils.hs b/libraries/base/Foreign/Marshal/Utils.hs
index 30e80035fa..f6bec7aacb 100644
--- a/libraries/base/Foreign/Marshal/Utils.hs
+++ b/libraries/base/Foreign/Marshal/Utils.hs
@@ -6,7 +6,7 @@
-- Module : Foreign.Marshal.Utils
-- Copyright : (c) The FFI task force 2001
-- License : BSD-style (see the file libraries/base/LICENSE)
---
+--
-- Maintainer : ffi@haskell.org
-- Stability : provisional
-- Portability : portable
@@ -72,8 +72,8 @@ import GHC.Base
-- 'Foreign.Marshal.Alloc.finalizerFree' when no longer required.
--
new :: Storable a => a -> IO (Ptr a)
-new val =
- do
+new val =
+ do
ptr <- malloc
poke ptr val
return ptr
@@ -122,12 +122,12 @@ maybeNew = maybe (return nullPtr)
-- |Converts a @withXXX@ combinator into one marshalling a value wrapped
-- into a 'Maybe', using 'nullPtr' to represent 'Nothing'.
--
-maybeWith :: ( a -> (Ptr b -> IO c) -> IO c)
+maybeWith :: ( a -> (Ptr b -> IO c) -> IO c)
-> (Maybe a -> (Ptr b -> IO c) -> IO c)
maybeWith = maybe ($ nullPtr)
-- |Convert a peek combinator into a one returning 'Nothing' if applied to a
--- 'nullPtr'
+-- 'nullPtr'
--
maybePeek :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek peek ptr | ptr == nullPtr = return Nothing
@@ -155,16 +155,26 @@ withMany withFoo (x:xs) f = withFoo x $ \x' ->
-- |Copies the given number of bytes from the second area (source) into the
-- first (destination); the copied areas may /not/ overlap
--
-copyBytes :: Ptr a -> Ptr a -> Int -> IO ()
-copyBytes dest src size = do _ <- memcpy dest src (fromIntegral size)
- return ()
+copyBytes
+ :: Ptr a -- ^ Destination
+ -> Ptr a -- ^ Source
+ -> Int -- ^ Size in bytes
+ -> IO ()
+copyBytes dest src size = do
+ _ <- memcpy dest src (fromIntegral size)
+ return ()
-- |Copies the given number of bytes from the second area (source) into the
-- first (destination); the copied areas /may/ overlap
--
-moveBytes :: Ptr a -> Ptr a -> Int -> IO ()
-moveBytes dest src size = do _ <- memmove dest src (fromIntegral size)
- return ()
+moveBytes
+ :: Ptr a -- ^ Destination
+ -> Ptr a -- ^ Source
+ -> Int -- ^ Size in bytes
+ -> IO ()
+moveBytes dest src size = do
+ _ <- memmove dest src (fromIntegral size)
+ return ()
-- Filling up memory area with required values
-- -------------------------------------------
diff --git a/libraries/base/GHC/Event/Thread.hs b/libraries/base/GHC/Event/Thread.hs
index a9d5410d9c..ad922d73f2 100644
--- a/libraries/base/GHC/Event/Thread.hs
+++ b/libraries/base/GHC/Event/Thread.hs
@@ -281,7 +281,7 @@ startIOManagerThread eventManagerArray i = do
ThreadFinished -> create
ThreadDied -> do
-- Sanity check: if the thread has died, there is a chance
- -- that event manager is still alive. This could happend during
+ -- that event manager is still alive. This could happened during
-- the fork, for example. In this case we should clean up
-- open pipes and everything else related to the event manager.
-- See #4449
@@ -308,7 +308,7 @@ startTimerManagerThread = modifyMVar_ timerManagerThreadVar $ \old -> do
ThreadFinished -> create
ThreadDied -> do
-- Sanity check: if the thread has died, there is a chance
- -- that event manager is still alive. This could happend during
+ -- that event manager is still alive. This could happened during
-- the fork, for example. In this case we should clean up
-- open pipes and everything else related to the event manager.
-- See #4449
diff --git a/libraries/base/GHC/IO/Handle/Lock/LinuxOFD.hsc b/libraries/base/GHC/IO/Handle/Lock/LinuxOFD.hsc
index 1046fa9351..5e4e642009 100644
--- a/libraries/base/GHC/IO/Handle/Lock/LinuxOFD.hsc
+++ b/libraries/base/GHC/IO/Handle/Lock/LinuxOFD.hsc
@@ -12,8 +12,8 @@ module GHC.IO.Handle.Lock.LinuxOFD where
import GHC.Base () -- Make implicit dependency known to build system
#else
-#include <sys/unistd.h>
-#include <sys/fcntl.h>
+#include <unistd.h>
+#include <fcntl.h>
import Data.Function
import Data.Functor
diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs
index 3185418d54..71bc3f0ce4 100644
--- a/libraries/base/GHC/Int.hs
+++ b/libraries/base/GHC/Int.hs
@@ -179,10 +179,10 @@ instance Bits Int8 where
{-# INLINE testBit #-}
{-# INLINE popCount #-}
- (I8# x#) .&. (I8# y#) = I8# (word2Int# (int2Word# x# `and#` int2Word# y#))
- (I8# x#) .|. (I8# y#) = I8# (word2Int# (int2Word# x# `or#` int2Word# y#))
- (I8# x#) `xor` (I8# y#) = I8# (word2Int# (int2Word# x# `xor#` int2Word# y#))
- complement (I8# x#) = I8# (word2Int# (not# (int2Word# x#)))
+ (I8# x#) .&. (I8# y#) = I8# (x# `andI#` y#)
+ (I8# x#) .|. (I8# y#) = I8# (x# `orI#` y#)
+ (I8# x#) `xor` (I8# y#) = I8# (x# `xorI#` y#)
+ complement (I8# x#) = I8# (notI# x#)
(I8# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = I8# (narrow8Int# (x# `iShiftL#` i#))
| otherwise = I8# (x# `iShiftRA#` negateInt# i#)
@@ -386,10 +386,10 @@ instance Bits Int16 where
{-# INLINE testBit #-}
{-# INLINE popCount #-}
- (I16# x#) .&. (I16# y#) = I16# (word2Int# (int2Word# x# `and#` int2Word# y#))
- (I16# x#) .|. (I16# y#) = I16# (word2Int# (int2Word# x# `or#` int2Word# y#))
- (I16# x#) `xor` (I16# y#) = I16# (word2Int# (int2Word# x# `xor#` int2Word# y#))
- complement (I16# x#) = I16# (word2Int# (not# (int2Word# x#)))
+ (I16# x#) .&. (I16# y#) = I16# (x# `andI#` y#)
+ (I16# x#) .|. (I16# y#) = I16# (x# `orI#` y#)
+ (I16# x#) `xor` (I16# y#) = I16# (x# `xorI#` y#)
+ complement (I16# x#) = I16# (notI# x#)
(I16# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = I16# (narrow16Int# (x# `iShiftL#` i#))
| otherwise = I16# (x# `iShiftRA#` negateInt# i#)
@@ -595,10 +595,10 @@ instance Bits Int32 where
{-# INLINE testBit #-}
{-# INLINE popCount #-}
- (I32# x#) .&. (I32# y#) = I32# (word2Int# (int2Word# x# `and#` int2Word# y#))
- (I32# x#) .|. (I32# y#) = I32# (word2Int# (int2Word# x# `or#` int2Word# y#))
- (I32# x#) `xor` (I32# y#) = I32# (word2Int# (int2Word# x# `xor#` int2Word# y#))
- complement (I32# x#) = I32# (word2Int# (not# (int2Word# x#)))
+ (I32# x#) .&. (I32# y#) = I32# (x# `andI#` y#)
+ (I32# x#) .|. (I32# y#) = I32# (x# `orI#` y#)
+ (I32# x#) `xor` (I32# y#) = I32# (x# `xorI#` y#)
+ complement (I32# x#) = I32# (notI# x#)
(I32# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = I32# (narrow32Int# (x# `iShiftL#` i#))
| otherwise = I32# (x# `iShiftRA#` negateInt# i#)
@@ -1014,10 +1014,10 @@ instance Bits Int64 where
{-# INLINE testBit #-}
{-# INLINE popCount #-}
- (I64# x#) .&. (I64# y#) = I64# (word2Int# (int2Word# x# `and#` int2Word# y#))
- (I64# x#) .|. (I64# y#) = I64# (word2Int# (int2Word# x# `or#` int2Word# y#))
- (I64# x#) `xor` (I64# y#) = I64# (word2Int# (int2Word# x# `xor#` int2Word# y#))
- complement (I64# x#) = I64# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
+ (I64# x#) .&. (I64# y#) = I64# (x# `andI#` y#)
+ (I64# x#) .|. (I64# y#) = I64# (x# `orI#` y#)
+ (I64# x#) `xor` (I64# y#) = I64# (x# `xorI#` y#)
+ complement (I64# x#) = I64# (notI# x#)
(I64# x#) `shift` (I# i#)
| isTrue# (i# >=# 0#) = I64# (x# `iShiftL#` i#)
| otherwise = I64# (x# `iShiftRA#` negateInt# i#)
diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs
index 6f6d9d670a..65fa4f54a5 100644
--- a/libraries/base/GHC/List.hs
+++ b/libraries/base/GHC/List.hs
@@ -87,7 +87,7 @@ last [] = errorEmptyList "last"
#else
-- Use foldl to make last a good consumer.
-- This will compile to good code for the actual GHC.List.last.
--- (At least as long it is eta-expaned, otherwise it does not, #10260.)
+-- (At least as long it is eta-expanded, otherwise it does not, #10260.)
last xs = foldl (\_ x -> x) lastError xs
{-# INLINE last #-}
-- The inline pragma is required to make GHC remember the implementation via
@@ -400,7 +400,7 @@ strictUncurryScanr f pair = case pair of
scanrFB :: (a -> b -> b) -> (b -> c -> c) -> a -> (b, c) -> (b, c)
scanrFB f c = \x ~(r, est) -> (f x r, r `c` est)
-- This lazy pattern match on the tuple is necessary to prevent
--- an infinite loop when scanr recieves a fusable infinite list,
+-- an infinite loop when scanr receives a fusable infinite list,
-- which was the reason for #16943.
-- See Note [scanrFB and evaluation] below
diff --git a/libraries/base/GHC/Read.hs b/libraries/base/GHC/Read.hs
index a79f405079..14e4a9b7e2 100644
--- a/libraries/base/GHC/Read.hs
+++ b/libraries/base/GHC/Read.hs
@@ -414,7 +414,7 @@ readSymField fieldName readVal = do
-- typecheck/TcGenDeriv.hs) would generate inline code for parsing fields;
-- this, however, turned out to produce massive amounts of intermediate code,
-- and produced a considerable performance hit in the code generator.
--- Since Read instances are not generally supposed to be perfomance critical,
+-- Since Read instances are not generally supposed to be performance critical,
-- the readField and readSymField functions have been factored out, and the
-- code generator now just generates calls rather than manually inlining the
-- parsers. For large record types (e.g. 500 fields), this produces a
diff --git a/libraries/base/System/CPUTime.hsc b/libraries/base/System/CPUTime.hsc
index 6bc90f168a..5b0fdbf4da 100644
--- a/libraries/base/System/CPUTime.hsc
+++ b/libraries/base/System/CPUTime.hsc
@@ -40,7 +40,7 @@ import qualified System.CPUTime.Posix.ClockGetTime as I
#elif defined(HAVE_GETRUSAGE) && ! solaris2_HOST_OS
import qualified System.CPUTime.Posix.RUsage as I
--- @getrusage()@ is right royal pain to deal with when targetting multiple
+-- @getrusage()@ is right royal pain to deal with when targeting multiple
-- versions of Solaris, since some versions supply it in libc (2.3 and 2.5),
-- while 2.4 has got it in libucb (I wouldn't be too surprised if it was back
-- again in libucb in 2.6..)
diff --git a/libraries/base/System/Environment/ExecutablePath.hsc b/libraries/base/System/Environment/ExecutablePath.hsc
index 3c9d36cb88..cdf39ea041 100644
--- a/libraries/base/System/Environment/ExecutablePath.hsc
+++ b/libraries/base/System/Environment/ExecutablePath.hsc
@@ -39,6 +39,7 @@ import Foreign.Marshal.Array
import Foreign.Ptr
import Foreign.Storable
import System.Posix.Internals
+#include <sys/types.h>
#include <sys/sysctl.h>
#elif defined(mingw32_HOST_OS)
import Control.Exception
diff --git a/libraries/base/System/IO/Error.hs b/libraries/base/System/IO/Error.hs
index 2585181df8..3417b910e5 100644
--- a/libraries/base/System/IO/Error.hs
+++ b/libraries/base/System/IO/Error.hs
@@ -176,7 +176,7 @@ isUserError = isUserErrorType . ioeGetErrorType
-- | An error indicating that the operation failed because the
-- resource vanished. See 'resourceVanishedErrorType'.
--
--- @since 0.4.14.0
+-- @since 4.14.0.0
isResourceVanishedError :: IOError -> Bool
isResourceVanishedError = isResourceVanishedErrorType . ioeGetErrorType
@@ -224,7 +224,7 @@ userErrorType = UserError
-- This happens when, for example, attempting to write to a closed
-- socket or attempting to write to a named pipe that was deleted.
--
--- @since 0.4.14.0
+-- @since 4.14.0.0
resourceVanishedErrorType :: IOErrorType
resourceVanishedErrorType = ResourceVanished
@@ -279,7 +279,7 @@ isUserErrorType _ = False
-- | I\/O error where the operation failed because the resource vanished.
-- See 'resourceVanishedErrorType'.
--
--- @since 0.4.14.0
+-- @since 4.14.0.0
isResourceVanishedErrorType :: IOErrorType -> Bool
isResourceVanishedErrorType ResourceVanished = True
isResourceVanishedErrorType _ = False
diff --git a/libraries/base/tests/IO/T2122.hs b/libraries/base/tests/IO/T2122.hs
index 488d2434bc..2969cdaf28 100644
--- a/libraries/base/tests/IO/T2122.hs
+++ b/libraries/base/tests/IO/T2122.hs
@@ -34,7 +34,7 @@ main = do
writeFile fp "test"
test True
--- fails everytime when causeFailure is True in GHCi, with runhaskell,
+-- fails every time when causeFailure is True in GHCi, with runhaskell,
-- or when compiled.
test :: Bool -> IO ()
test causeFailure =