From 272573c62db9363875d953214540588ba7b73ba5 Mon Sep 17 00:00:00 2001 From: Ben Gamari <ben@smart-cactus.org> Date: Thu, 22 Feb 2024 01:48:23 -0500 Subject: [PATCH] Move Haddock named chunks --- libraries/base/src/Control/Exception.hs | 206 ++++ libraries/base/src/Control/Monad.hs | 25 + libraries/base/src/Data/IORef.hs | 54 +- libraries/base/src/Data/Int.hs | 27 +- libraries/base/src/Debug/Trace.hs | 50 + libraries/base/src/Foreign/StablePtr.hs | 16 +- libraries/base/src/GHC/ForeignPtr.hs | 45 + .../src/GHC/Internal/Conc/Sync.hs | 2 +- .../src/GHC/Internal/Control/Exception.hs | 234 ---- .../src/GHC/Internal/Control/Monad.hs | 34 +- .../src/GHC/Internal/Control/Monad/Fail.hs | 25 - .../src/GHC/Internal/Control/Monad/Fix.hs | 8 +- .../src/GHC/Internal/Data/Either.hs | 4 +- .../src/GHC/Internal/Data/Foldable.hs | 1089 +--------------- .../src/GHC/Internal/Data/IORef.hs | 55 - .../ghc-internal/src/GHC/Internal/Data/Int.hs | 39 +- .../src/GHC/Internal/Data/Traversable.hs | 1093 +---------------- .../GHC/Internal/Data/Typeable/Internal.hs | 2 +- .../src/GHC/Internal/Debug/Trace.hs | 53 - .../src/GHC/Internal/Debug/Trace.hs-boot | 8 - .../src/GHC/Internal/Foreign/StablePtr.hs | 16 - .../src/GHC/Internal/ForeignPtr.hs | 44 - .../src/GHC/Internal/System/IO.hs | 22 - 23 files changed, 458 insertions(+), 2693 deletions(-) diff --git a/libraries/base/src/Control/Exception.hs b/libraries/base/src/Control/Exception.hs index 5c86c02a9bc4..b22ffeb401f0 100644 --- a/libraries/base/src/Control/Exception.hs +++ b/libraries/base/src/Control/Exception.hs @@ -107,3 +107,209 @@ module Control.Exception ) where import GHC.Internal.Control.Exception + +{- $catching + +There are several functions for catching and examining +exceptions; all of them may only be used from within the +'IO' monad. + +Here's a rule of thumb for deciding which catch-style function to +use: + + * If you want to do some cleanup in the event that an exception + is raised, use 'finally', 'bracket' or 'onException'. + + * To recover after an exception and do something else, the best + choice is to use one of the 'try' family. + + * ... unless you are recovering from an asynchronous exception, in which + case use 'catch' or 'catchJust'. + +The difference between using 'try' and 'catch' for recovery is that in +'catch' the handler is inside an implicit 'mask' (see \"Asynchronous +Exceptions\") which is important when catching asynchronous +exceptions, but when catching other kinds of exception it is +unnecessary. Furthermore it is possible to accidentally stay inside +the implicit 'mask' by tail-calling rather than returning from the +handler, which is why we recommend using 'try' rather than 'catch' for +ordinary exception recovery. + +A typical use of 'tryJust' for recovery looks like this: + +> do r <- tryJust (guard . isDoesNotExistError) $ getEnv "HOME" +> case r of +> Left e -> ... +> Right home -> ... + +-} + +{- $async + + #AsynchronousExceptions# Asynchronous exceptions are so-called because they arise due to +external influences, and can be raised at any point during execution. +'StackOverflow' and 'HeapOverflow' are two examples of +system-generated asynchronous exceptions. + +The primary source of asynchronous exceptions, however, is +'throwTo': + +> throwTo :: ThreadId -> Exception -> IO () + +'throwTo' (also 'Control.Concurrent.killThread') allows one +running thread to raise an arbitrary exception in another thread. The +exception is therefore asynchronous with respect to the target thread, +which could be doing anything at the time it receives the exception. +Great care should be taken with asynchronous exceptions; it is all too +easy to introduce race conditions by the over zealous use of +'throwTo'. +-} + +{- $block_handler +There\'s an implied 'mask' around every exception handler in a call +to one of the 'catch' family of functions. This is because that is +what you want most of the time - it eliminates a common race condition +in starting an exception handler, because there may be no exception +handler on the stack to handle another exception if one arrives +immediately. If asynchronous exceptions are masked on entering the +handler, though, we have time to install a new exception handler +before being interrupted. If this weren\'t the default, one would have +to write something like + +> mask $ \restore -> +> catch (restore (...)) +> (\e -> handler) + +If you need to unmask asynchronous exceptions again in the exception +handler, @restore@ can be used there too. + +Note that 'try' and friends /do not/ have a similar default, because +there is no exception handler in this case. Don't use 'try' for +recovering from an asynchronous exception. +-} + +{- $interruptible + + #interruptible# +Some operations are /interruptible/, which means that they can receive +asynchronous exceptions even in the scope of a 'mask'. Any function +which may itself block is defined as interruptible; this includes +'Control.Concurrent.MVar.takeMVar' +(but not 'Control.Concurrent.MVar.tryTakeMVar'), +and most operations which perform +some I\/O with the outside world. The reason for having +interruptible operations is so that we can write things like + +> mask $ \restore -> do +> a <- takeMVar m +> catch (restore (...)) +> (\e -> ...) + +if the 'Control.Concurrent.MVar.takeMVar' was not interruptible, +then this particular +combination could lead to deadlock, because the thread itself would be +blocked in a state where it can\'t receive any asynchronous exceptions. +With 'Control.Concurrent.MVar.takeMVar' interruptible, however, we can be +safe in the knowledge that the thread can receive exceptions right up +until the point when the 'Control.Concurrent.MVar.takeMVar' succeeds. +Similar arguments apply for other interruptible operations like +'System.IO.openFile'. + +It is useful to think of 'mask' not as a way to completely prevent +asynchronous exceptions, but as a way to switch from asynchronous mode +to polling mode. The main difficulty with asynchronous +exceptions is that they normally can occur anywhere, but within a +'mask' an asynchronous exception is only raised by operations that are +interruptible (or call other interruptible operations). In many cases +these operations may themselves raise exceptions, such as I\/O errors, +so the caller will usually be prepared to handle exceptions arising from the +operation anyway. To perform an explicit poll for asynchronous exceptions +inside 'mask', use 'allowInterrupt'. + +Sometimes it is too onerous to handle exceptions in the middle of a +critical piece of stateful code. There are three ways to handle this +kind of situation: + + * Use STM. Since a transaction is always either completely executed + or not at all, transactions are a good way to maintain invariants + over state in the presence of asynchronous (and indeed synchronous) + exceptions. + + * Use 'mask', and avoid interruptible operations. In order to do + this, we have to know which operations are interruptible. It is + impossible to know for any given library function whether it might + invoke an interruptible operation internally; so instead we give a + list of guaranteed-not-to-be-interruptible operations below. + + * Use 'uninterruptibleMask'. This is generally not recommended, + unless you can guarantee that any interruptible operations invoked + during the scope of 'uninterruptibleMask' can only ever block for + a short time. Otherwise, 'uninterruptibleMask' is a good way to + make your program deadlock and be unresponsive to user interrupts. + +The following operations are guaranteed not to be interruptible: + + * operations on 'Data.IORef.IORef' from "Data.IORef" + + * STM transactions that do not use 'Conc.retry' + + * everything from the @Foreign@ modules + + * everything from "Control.Exception" except for 'throwTo' + + * 'Control.Concurrent.MVar.tryTakeMVar', 'Control.Concurrent.MVar.tryPutMVar', + 'Control.Concurrent.MVar.isEmptyMVar' + + * 'Control.Concurrent.MVar.takeMVar' if the 'Control.Concurrent.MVar.MVar' is + definitely full, and conversely 'Control.Concurrent.MVar.putMVar' if the + 'Control.Concurrent.MVar.MVar' is definitely empty + + * 'Control.Concurrent.MVar.newEmptyMVar', 'Control.Concurrent.MVar.newMVar' + + * 'Control.Concurrent.forkIO', 'Control.Concurrent.myThreadId' + +-} + +{- $catchall + +It is possible to catch all exceptions, by using the type 'SomeException': + +> catch f (\e -> ... (e :: SomeException) ...) + +HOWEVER, this is normally not what you want to do! + +For example, suppose you want to read a file, but if it doesn't exist +then continue as if it contained \"\". You might be tempted to just +catch all exceptions and return \"\" in the handler. However, this has +all sorts of undesirable consequences. For example, if the user +presses control-C at just the right moment then the 'UserInterrupt' +exception will be caught, and the program will continue running under +the belief that the file contains \"\". Similarly, if another thread +tries to kill the thread reading the file then the 'ThreadKilled' +exception will be ignored. + +Instead, you should only catch exactly the exceptions that you really +want. In this case, this would likely be more specific than even +\"any IO exception\"; a permissions error would likely also want to be +handled differently. Instead, you would probably want something like: + +> e <- tryJust (guard . isDoesNotExistError) (readFile f) +> let str = either (const "") id e + +There are occasions when you really do need to catch any sort of +exception. However, in most cases this is just so you can do some +cleaning up; you aren't actually interested in the exception itself. +For example, if you open a file then you want to close it again, +whether processing the file executes normally or throws an exception. +However, in these cases you can use functions like 'bracket', 'finally' +and 'onException', which never actually pass you the exception, but +just call the cleanup functions at the appropriate points. + +But sometimes you really do need to catch any exception, and actually +see what the exception is. One example is at the very top-level of a +program, you may wish to catch any exception, print it to a logfile or +the screen, and then exit gracefully. For these cases, you can use +'catch' (or one of the other exception-catching functions) with the +'SomeException' type. +-} + diff --git a/libraries/base/src/Control/Monad.hs b/libraries/base/src/Control/Monad.hs index 21fd6a3aef77..6e2bd72db8cf 100644 --- a/libraries/base/src/Control/Monad.hs +++ b/libraries/base/src/Control/Monad.hs @@ -62,3 +62,28 @@ module Control.Monad ) where import GHC.Internal.Control.Monad + +{- $naming + +The functions in this library use the following naming conventions: + +* A postfix \'@M@\' always stands for a function in the Kleisli category: + The monad type constructor @m@ is added to function results + (modulo currying) and nowhere else. So, for example, + +> filter :: (a -> Bool) -> [a] -> [a] +> filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a] + +* A postfix \'@_@\' changes the result type from @(m a)@ to @(m ())@. + Thus, for example: + +> sequence :: Monad m => [m a] -> m [a] +> sequence_ :: Monad m => [m a] -> m () + +* A prefix \'@m@\' generalizes an existing function to a monadic form. + Thus, for example: + +> filter :: (a -> Bool) -> [a] -> [a] +> mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a + +-} diff --git a/libraries/base/src/Data/IORef.hs b/libraries/base/src/Data/IORef.hs index 23e086b6c8d4..e9978593821d 100644 --- a/libraries/base/src/Data/IORef.hs +++ b/libraries/base/src/Data/IORef.hs @@ -29,4 +29,56 @@ module Data.IORef -- $memmodel ) where -import GHC.Internal.Data.IORef \ No newline at end of file +import GHC.Internal.Data.IORef + +{- $memmodel + #memmodel# + + Most modern CPU achitectures (e.g. x86/64, ARM) have a memory model which allows + threads to reorder reads with earlier writes to different locations, + e.g. see <https://www.intel.com/content/www/us/en/developer/articles/technical/intel-sdm.html the x86/64 architecture manual>, + 8.2.3.4 Loads May Be Reordered with Earlier Stores to Different Locations. + + Because of that, in a concurrent program, 'IORef' operations may appear out-of-order + to another thread. In the following example: + + > import GHC.Internal.Data.IORef + > import GHC.Internal.Control.Monad (unless) + > import Control.Concurrent (forkIO, threadDelay) + > + > maybePrint :: IORef Bool -> IORef Bool -> IO () + > maybePrint myRef yourRef = do + > writeIORef myRef True + > yourVal <- readIORef yourRef + > unless yourVal $ putStrLn "critical section" + > + > main :: IO () + > main = do + > r1 <- newIORef False + > r2 <- newIORef False + > forkIO $ maybePrint r1 r2 + > forkIO $ maybePrint r2 r1 + > threadDelay 1000000 + + it is possible that the string @"critical section"@ is printed + twice, even though there is no interleaving of the operations of the + two threads that allows that outcome. The memory model of x86/64 + allows 'readIORef' to happen before the earlier 'writeIORef'. + + The ARM memory order model is typically even weaker than x86/64, allowing + any reordering of reads and writes as long as they are independent + from the point of view of the current thread. + + The implementation is required to ensure that reordering of memory + operations cannot cause type-correct code to go wrong. In + particular, when inspecting the value read from an 'IORef', the + memory writes that created that value must have occurred from the + point of view of the current thread. + + 'atomicWriteIORef', 'atomicModifyIORef' and 'atomicModifyIORef'' act + as a barrier to reordering. Multiple calls to these functions + occur in strict program order, never taking place ahead of any + earlier (in program order) 'IORef' operations, or after any later + 'IORef' operations. + +-} diff --git a/libraries/base/src/Data/Int.hs b/libraries/base/src/Data/Int.hs index be248e5b8fcd..f14730b47225 100644 --- a/libraries/base/src/Data/Int.hs +++ b/libraries/base/src/Data/Int.hs @@ -24,4 +24,29 @@ module Data.Int -- $notes ) where -import GHC.Internal.Data.Int \ No newline at end of file +import GHC.Internal.Data.Int + +{- $notes + +* All arithmetic is performed modulo 2^n, where @n@ is the number of + bits in the type. + +* For coercing between any two integer types, use 'Prelude.fromIntegral', + which is specialized for all the common cases so should be fast + enough. Coercing word types (see "Data.Word") to and from integer + types preserves representation, not sign. + +* The rules that hold for 'Prelude.Enum' instances over a + bounded type such as 'Int' (see the section of the + Haskell report dealing with arithmetic sequences) also hold for the + 'Prelude.Enum' instances over the various + 'Int' types defined here. + +* Right and left shifts by amounts greater than or equal to the width + of the type result in either zero or -1, depending on the sign of + the value being shifted. This is contrary to the behaviour in C, + which is undefined; a common interpretation is to truncate the shift + count to the width of the type, for example @1 \<\< 32 + == 1@ in some C implementations. +-} + diff --git a/libraries/base/src/Debug/Trace.hs b/libraries/base/src/Debug/Trace.hs index b9d9e0f4b687..81190a2d051b 100644 --- a/libraries/base/src/Debug/Trace.hs +++ b/libraries/base/src/Debug/Trace.hs @@ -43,3 +43,53 @@ module Debug.Trace ) where import GHC.Internal.Debug.Trace + +-- $setup +-- >>> import Prelude + +-- $tracing +-- +-- The 'trace', 'traceShow' and 'traceIO' functions print messages to an output +-- stream. They are intended for \"printf debugging\", that is: tracing the flow +-- of execution and printing interesting values. +-- +-- All these functions evaluate the message completely before printing +-- it; so if the message is not fully defined, none of it will be +-- printed. +-- +-- The usual output stream is 'GHC.Internal.System.IO.stderr'. For Windows GUI applications +-- (that have no stderr) the output is directed to the Windows debug console. +-- Some implementations of these functions may decorate the string that\'s +-- output to indicate that you\'re tracing. + +-- $eventlog_tracing +-- +-- Eventlog tracing is a performance profiling system. These functions emit +-- extra events into the eventlog. In combination with eventlog profiling +-- tools these functions can be used for monitoring execution and +-- investigating performance problems. +-- +-- Currently only GHC provides eventlog profiling, see the GHC user guide for +-- details on how to use it. These function exists for other Haskell +-- implementations but no events are emitted. Note that the string message is +-- always evaluated, whether or not profiling is available or enabled. + +-- $markers +-- +-- When looking at a profile for the execution of a program we often want to +-- be able to mark certain points or phases in the execution and see that +-- visually in the profile. +-- +-- For example, a program might have several distinct phases with different +-- performance or resource behaviour in each phase. To properly interpret the +-- profile graph we really want to see when each phase starts and ends. +-- +-- Markers let us do this: we can annotate the program to emit a marker at +-- an appropriate point during execution and then see that in a profile. +-- +-- Currently this feature is only supported in GHC by the eventlog tracing +-- system, but in future it may also be supported by the heap profiling or +-- other profiling tools. These function exists for other Haskell +-- implementations but they have no effect. Note that the string message is +-- always evaluated, whether or not profiling is available or enabled. + diff --git a/libraries/base/src/Foreign/StablePtr.hs b/libraries/base/src/Foreign/StablePtr.hs index 75cf25e396e1..8841ed6ffe18 100644 --- a/libraries/base/src/Foreign/StablePtr.hs +++ b/libraries/base/src/Foreign/StablePtr.hs @@ -26,4 +26,18 @@ module Foreign.StablePtr -- $cinterface ) where -import GHC.Internal.Foreign.StablePtr \ No newline at end of file +import GHC.Internal.Foreign.StablePtr + +-- $cinterface +-- +-- The following definition is available to C programs inter-operating with +-- Haskell code when including the header @HsFFI.h@. +-- +-- > typedef void *HsStablePtr; /* C representation of a StablePtr */ +-- +-- Note that no assumptions may be made about the values representing stable +-- pointers. In fact, they need not even be valid memory addresses. The only +-- guarantee provided is that if they are passed back to Haskell land, the +-- function 'deRefStablePtr' will be able to reconstruct the +-- Haskell value referred to by the stable pointer. + diff --git a/libraries/base/src/GHC/ForeignPtr.hs b/libraries/base/src/GHC/ForeignPtr.hs index 16bbff053780..443faf765796 100644 --- a/libraries/base/src/GHC/ForeignPtr.hs +++ b/libraries/base/src/GHC/ForeignPtr.hs @@ -43,6 +43,51 @@ module GHC.ForeignPtr touchForeignPtr, -- * Finalization finalizeForeignPtr + -- * Commentary + -- $commentary ) where import GHC.Internal.ForeignPtr + +{- $commentary + +This is a high-level overview of how 'ForeignPtr' works. +The implementation of 'ForeignPtr' must accomplish several goals: + +1. Invoke a finalizer once a foreign pointer becomes unreachable. +2. Support augmentation of finalizers, i.e. 'addForeignPtrFinalizer'. + As a motivating example, suppose that the payload of a foreign + pointer is C struct @bar@ that has an optionally NULL pointer field + @foo@ to an unmanaged heap object. Initially, @foo@ is NULL, and + later the program uses @malloc@, initializes the object, and assigns + @foo@ the address returned by @malloc@. When the foreign pointer + becomes unreachable, it is now necessary to first @free@ the object + pointed to by @foo@ and then invoke whatever finalizer was associated + with @bar@. That is, finalizers must be invoked in the opposite order + they are added. +3. Allow users to invoke a finalizer promptly if they know that the + foreign pointer is unreachable, i.e. 'finalizeForeignPtr'. + +How can these goals be accomplished? Goal 1 suggests that weak references +and finalizers (via 'Weak#' and 'mkWeak#') are necessary. But how should +they be used and what should their key be? Certainly not 'ForeignPtr' or +'ForeignPtrContents'. See the warning in "GHC.Weak" about weak pointers with +lifted (non-primitive) keys. The two finalizer-supporting data constructors of +'ForeignPtr' have an @'IORef' 'Finalizers'@ (backed by 'MutVar#') field. +This gets used in two different ways depending on the kind of finalizer: + +* 'HaskellFinalizers': The first @addForeignPtrConcFinalizer_@ call uses + 'mkWeak#' to attach the finalizer @foreignPtrFinalizer@ to the 'MutVar#'. + The resulting 'Weak#' is discarded (see @addForeignPtrConcFinalizer_@). + Subsequent calls to @addForeignPtrConcFinalizer_@ (goal 2) just add + finalizers onto the list in the 'HaskellFinalizers' data constructor. +* 'CFinalizers': The first 'addForeignPtrFinalizer' call uses + 'mkWeakNoFinalizer#' to create a 'Weak#'. The 'Weak#' is preserved in the + 'CFinalizers' data constructor. Both the first call and subsequent + calls (goal 2) use 'addCFinalizerToWeak#' to attach finalizers to the + 'Weak#' itself. Also, see Note [MallocPtr finalizers] for discussion of + the key and value of this 'Weak#'. + +In either case, the runtime invokes the appropriate finalizers when the +'ForeignPtr' becomes unreachable. +-} diff --git a/libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs b/libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs index b0ad0bbe6d25..017ecb28d225 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs @@ -271,7 +271,7 @@ thread; if you need foreign calls to be made by a particular OS thread, then use 'Control.Concurrent.forkOS' instead. The new thread inherits the /masked/ state of the parent (see -'GHC.Internal.Control.Exception.mask'). +'GHC.Control.Exception.mask'). The newly created thread has an exception handler that discards the exceptions 'BlockedIndefinitelyOnMVar', 'BlockedIndefinitelyOnSTM', and diff --git a/libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs b/libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs index 5e2fa92bdad6..4695c2e7d3ed 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs @@ -65,14 +65,6 @@ module GHC.Internal.Control.Exception ( ioError, throwTo, - -- * Catching Exceptions - - -- $catching - - -- ** Catching all exceptions - - -- $catchall - -- ** The @catch@ functions catch, catches, Handler(..), @@ -92,15 +84,7 @@ module GHC.Internal.Control.Exception ( -- ** The @mapException@ function mapException, - -- * Asynchronous Exceptions - - -- $async - -- ** Asynchronous exception control - - -- |The following functions allow a thread to control delivery of - -- asynchronous exceptions during a critical region. - mask, mask_, uninterruptibleMask, @@ -110,20 +94,10 @@ module GHC.Internal.Control.Exception ( interruptible, allowInterrupt, - -- *** Applying @mask@ to an exception handler - - -- $block_handler - - -- *** Interruptible operations - - -- $interruptible - -- * Assertions - assert, -- * Utilities - bracket, bracket_, bracketOnError, @@ -173,45 +147,6 @@ catchesHandler handlers e = foldr tryHandler (throw e) handlers Just e' -> handler e' Nothing -> res --- ----------------------------------------------------------------------------- --- Catching exceptions - -{- $catching - -There are several functions for catching and examining -exceptions; all of them may only be used from within the -'IO' monad. - -Here's a rule of thumb for deciding which catch-style function to -use: - - * If you want to do some cleanup in the event that an exception - is raised, use 'finally', 'bracket' or 'onException'. - - * To recover after an exception and do something else, the best - choice is to use one of the 'try' family. - - * ... unless you are recovering from an asynchronous exception, in which - case use 'catch' or 'catchJust'. - -The difference between using 'try' and 'catch' for recovery is that in -'catch' the handler is inside an implicit 'mask' (see \"Asynchronous -Exceptions\") which is important when catching asynchronous -exceptions, but when catching other kinds of exception it is -unnecessary. Furthermore it is possible to accidentally stay inside -the implicit 'mask' by tail-calling rather than returning from the -handler, which is why we recommend using 'try' rather than 'catch' for -ordinary exception recovery. - -A typical use of 'tryJust' for recovery looks like this: - -> do r <- tryJust (guard . isDoesNotExistError) $ getEnv "HOME" -> case r of -> Left e -> ... -> Right home -> ... - --} - -- ----------------------------------------------------------------------------- -- Asynchronous exceptions @@ -227,172 +162,3 @@ A typical use of 'tryJust' for recovery looks like this: allowInterrupt :: IO () allowInterrupt = interruptible $ return () -{- $async - - #AsynchronousExceptions# Asynchronous exceptions are so-called because they arise due to -external influences, and can be raised at any point during execution. -'StackOverflow' and 'HeapOverflow' are two examples of -system-generated asynchronous exceptions. - -The primary source of asynchronous exceptions, however, is -'throwTo': - -> throwTo :: ThreadId -> Exception -> IO () - -'throwTo' (also 'Control.Concurrent.killThread') allows one -running thread to raise an arbitrary exception in another thread. The -exception is therefore asynchronous with respect to the target thread, -which could be doing anything at the time it receives the exception. -Great care should be taken with asynchronous exceptions; it is all too -easy to introduce race conditions by the over zealous use of -'throwTo'. --} - -{- $block_handler -There\'s an implied 'mask' around every exception handler in a call -to one of the 'catch' family of functions. This is because that is -what you want most of the time - it eliminates a common race condition -in starting an exception handler, because there may be no exception -handler on the stack to handle another exception if one arrives -immediately. If asynchronous exceptions are masked on entering the -handler, though, we have time to install a new exception handler -before being interrupted. If this weren\'t the default, one would have -to write something like - -> mask $ \restore -> -> catch (restore (...)) -> (\e -> handler) - -If you need to unmask asynchronous exceptions again in the exception -handler, @restore@ can be used there too. - -Note that 'try' and friends /do not/ have a similar default, because -there is no exception handler in this case. Don't use 'try' for -recovering from an asynchronous exception. --} - -{- $interruptible - - #interruptible# -Some operations are /interruptible/, which means that they can receive -asynchronous exceptions even in the scope of a 'mask'. Any function -which may itself block is defined as interruptible; this includes -'GHC.Internal.Control.Concurrent.MVar.takeMVar' -(but not 'GHC.Internal.Control.Concurrent.MVar.tryTakeMVar'), -and most operations which perform -some I\/O with the outside world. The reason for having -interruptible operations is so that we can write things like - -> mask $ \restore -> do -> a <- takeMVar m -> catch (restore (...)) -> (\e -> ...) - -if the 'GHC.Internal.Control.Concurrent.MVar.takeMVar' was not interruptible, -then this particular -combination could lead to deadlock, because the thread itself would be -blocked in a state where it can\'t receive any asynchronous exceptions. -With 'GHC.Internal.Control.Concurrent.MVar.takeMVar' interruptible, however, we can be -safe in the knowledge that the thread can receive exceptions right up -until the point when the 'GHC.Internal.Control.Concurrent.MVar.takeMVar' succeeds. -Similar arguments apply for other interruptible operations like -'GHC.Internal.System.IO.openFile'. - -It is useful to think of 'mask' not as a way to completely prevent -asynchronous exceptions, but as a way to switch from asynchronous mode -to polling mode. The main difficulty with asynchronous -exceptions is that they normally can occur anywhere, but within a -'mask' an asynchronous exception is only raised by operations that are -interruptible (or call other interruptible operations). In many cases -these operations may themselves raise exceptions, such as I\/O errors, -so the caller will usually be prepared to handle exceptions arising from the -operation anyway. To perform an explicit poll for asynchronous exceptions -inside 'mask', use 'allowInterrupt'. - -Sometimes it is too onerous to handle exceptions in the middle of a -critical piece of stateful code. There are three ways to handle this -kind of situation: - - * Use STM. Since a transaction is always either completely executed - or not at all, transactions are a good way to maintain invariants - over state in the presence of asynchronous (and indeed synchronous) - exceptions. - - * Use 'mask', and avoid interruptible operations. In order to do - this, we have to know which operations are interruptible. It is - impossible to know for any given library function whether it might - invoke an interruptible operation internally; so instead we give a - list of guaranteed-not-to-be-interruptible operations below. - - * Use 'uninterruptibleMask'. This is generally not recommended, - unless you can guarantee that any interruptible operations invoked - during the scope of 'uninterruptibleMask' can only ever block for - a short time. Otherwise, 'uninterruptibleMask' is a good way to - make your program deadlock and be unresponsive to user interrupts. - -The following operations are guaranteed not to be interruptible: - - * operations on 'Data.IORef.IORef' from "Data.IORef" - - * STM transactions that do not use 'GHC.Internal.Conc.retry' - - * everything from the @Foreign@ modules - - * everything from "Control.Exception" except for 'throwTo' - - * 'GHC.Internal.Control.Concurrent.MVar.tryTakeMVar', 'GHC.Internal.Control.Concurrent.MVar.tryPutMVar', - 'GHC.Internal.Control.Concurrent.MVar.isEmptyMVar' - - * 'GHC.Internal.Control.Concurrent.MVar.takeMVar' if the 'Control.Concurrent.MVar.MVar' is - definitely full, and conversely 'GHC.Internal.Control.Concurrent.MVar.putMVar' if the - 'Control.Concurrent.MVar.MVar' is definitely empty - - * 'GHC.Internal.Control.Concurrent.MVar.newEmptyMVar', 'GHC.Internal.Control.Concurrent.MVar.newMVar' - - * 'Control.Concurrent.forkIO', 'Control.Concurrent.myThreadId' - --} - -{- $catchall - -It is possible to catch all exceptions, by using the type 'SomeException': - -> catch f (\e -> ... (e :: SomeException) ...) - -HOWEVER, this is normally not what you want to do! - -For example, suppose you want to read a file, but if it doesn't exist -then continue as if it contained \"\". You might be tempted to just -catch all exceptions and return \"\" in the handler. However, this has -all sorts of undesirable consequences. For example, if the user -presses control-C at just the right moment then the 'UserInterrupt' -exception will be caught, and the program will continue running under -the belief that the file contains \"\". Similarly, if another thread -tries to kill the thread reading the file then the 'ThreadKilled' -exception will be ignored. - -Instead, you should only catch exactly the exceptions that you really -want. In this case, this would likely be more specific than even -\"any IO exception\"; a permissions error would likely also want to be -handled differently. Instead, you would probably want something like: - -> e <- tryJust (guard . isDoesNotExistError) (readFile f) -> let str = either (const "") id e - -There are occasions when you really do need to catch any sort of -exception. However, in most cases this is just so you can do some -cleaning up; you aren't actually interested in the exception itself. -For example, if you open a file then you want to close it again, -whether processing the file executes normally or throws an exception. -However, in these cases you can use functions like 'bracket', 'finally' -and 'onException', which never actually pass you the exception, but -just call the cleanup functions at the appropriate points. - -But sometimes you really do need to catch any exception, and actually -see what the exception is. One example is at the very top-level of a -program, you may wish to catch any exception, print it to a logfile or -the screen, and then exit gracefully. For these cases, you can use -'catch' (or one of the other exception-catching functions) with the -'SomeException' type. --} - diff --git a/libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs b/libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs index 3be7433ae936..bc2d7e00bfa1 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs @@ -136,7 +136,7 @@ guard :: (Alternative f) => Bool -> f () guard True = pure () guard False = empty --- | This generalizes the list-based 'GHC.Internal.Data.List.filter' function. +-- | This generalizes the list-based 'Data.List.filter' function. -- -- > runIdentity (filterM (Identity . p) xs) == filter p xs -- @@ -255,7 +255,7 @@ zipWithM_ :: (Applicative m) => (a -> b -> m c) -> [a] -> [b] -> m () -- See Note [Fusion for zipN/zipWithN] in List.hs. zipWithM_ f xs ys = sequenceA_ (zipWith f xs ys) -{- | The 'foldM' function is analogous to 'GHC.Internal.Data.Foldable.foldl', except that its result is +{- | The 'foldM' function is analogous to 'Data.Foldable.foldl', except that its result is encapsulated in a monad. Note that 'foldM' works from left-to-right over the list arguments. This could be an issue where @('>>')@ and the `folded function' are not commutative. @@ -388,15 +388,15 @@ f <$!> m = do -- ----------------------------------------------------------------------------- -- Other MonadPlus functions --- | Direct 'MonadPlus' equivalent of 'GHC.Internal.Data.List.filter'. +-- | Direct 'MonadPlus' equivalent of 'Data.List.filter'. -- -- ==== __Examples__ -- --- The 'GHC.Internal.Data.List.filter' function is just 'mfilter' specialized to +-- The 'Data.List.filter' function is just 'mfilter' specialized to -- the list monad: -- -- @ --- 'GHC.Internal.Data.List.filter' = ( 'mfilter' :: (a -> Bool) -> [a] -> [a] ) +-- 'Data.List.filter' = ( 'mfilter' :: (a -> Bool) -> [a] -> [a] ) -- @ -- -- An example using 'mfilter' with the 'Maybe' monad: @@ -412,27 +412,3 @@ mfilter p ma = do a <- ma if p a then return a else mzero -{- $naming - -The functions in this library use the following naming conventions: - -* A postfix \'@M@\' always stands for a function in the Kleisli category: - The monad type constructor @m@ is added to function results - (modulo currying) and nowhere else. So, for example, - -> filter :: (a -> Bool) -> [a] -> [a] -> filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a] - -* A postfix \'@_@\' changes the result type from @(m a)@ to @(m ())@. - Thus, for example: - -> sequence :: Monad m => [m a] -> m [a] -> sequence_ :: Monad m => [m a] -> m () - -* A prefix \'@m@\' generalizes an existing function to a monadic form. - Thus, for example: - -> filter :: (a -> Bool) -> [a] -> [a] -> mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a - --} diff --git a/libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs b/libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs index 6ed5cb6763f0..2acd5e0ac40f 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs @@ -11,31 +11,6 @@ -- Stability : provisional -- Portability : portable -- --- Transitional module providing the 'MonadFail' class and primitive --- instances. --- --- This module can be imported for defining forward compatible --- 'MonadFail' instances: --- --- @ --- import qualified GHC.Internal.Control.Monad.Fail as Fail --- --- instance Monad Foo where --- (>>=) = {- ...bind impl... -} --- --- -- Provide legacy 'fail' implementation for when --- -- new-style MonadFail desugaring is not enabled. --- fail = Fail.fail --- --- instance Fail.MonadFail Foo where --- fail = {- ...fail implementation... -} --- @ --- --- See <https://gitlab.haskell.org/haskell/prime/-/wikis/libraries/proposals/monad-fail> --- for more details. --- --- @since base-4.9.0.0 --- module GHC.Internal.Control.Monad.Fail ( MonadFail(fail) ) where import GHC.Internal.Base (String, Monad(), Maybe(Nothing), IO(), failIO) diff --git a/libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs b/libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs index cf3f5fa0c16a..67fd92618100 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fix.hs @@ -44,13 +44,13 @@ import GHC.Internal.System.IO -- Instances of 'MonadFix' should satisfy the following laws: -- -- [Purity] --- @'mfix' ('GHC.Internal.Control.Monad.return' . h) = 'GHC.Internal.Control.Monad.return' ('fix' h)@ +-- @'mfix' ('Control.Monad.return' . h) = 'Control.Monad.return' ('fix' h)@ -- -- [Left shrinking (or Tightening)] -- @'mfix' (\\x -> a >>= \\y -> f x y) = a >>= \\y -> 'mfix' (\\x -> f x y)@ -- -- [Sliding] --- @'mfix' ('GHC.Internal.Control.Monad.liftM' h . f) = 'GHC.Internal.Control.Monad.liftM' h ('mfix' (f . h))@, +-- @'mfix' ('Control.Monad.liftM' h . f) = 'Control.Monad.liftM' h ('mfix' (f . h))@, -- for strict @h@. -- -- [Nesting] @@ -110,7 +110,7 @@ instance MonadFix (Either e) where instance MonadFix (ST s) where mfix = fixST --- Instances of GHC.Internal.Data.Monoid wrappers +-- Instances of Data.Monoid wrappers -- | @since base-4.8.0.0 instance MonadFix Dual where @@ -160,7 +160,7 @@ instance (MonadFix f, MonadFix g) => MonadFix (f :*: g) where fstP (a :*: _) = a sndP (_ :*: b) = b --- Instances for GHC.Internal.Data.Ord +-- Instances for Data.Ord -- | @since base-4.12.0.0 instance MonadFix Down where diff --git a/libraries/ghc-internal/src/GHC/Internal/Data/Either.hs b/libraries/ghc-internal/src/GHC/Internal/Data/Either.hs index 3aa658ea517c..4c4b58aa8051 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Data/Either.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Data/Either.hs @@ -259,7 +259,7 @@ partitionEithers = foldr (either left right) ([],[]) -- matching when one does not care about the value contained in the -- constructor: -- --- >>> import GHC.Internal.Control.Monad ( when ) +-- >>> import Control.Monad ( when ) -- >>> let report e = when (isLeft e) $ putStrLn "ERROR" -- >>> report (Right 1) -- >>> report (Left "parse error") @@ -290,7 +290,7 @@ isLeft (Right _) = False -- matching when one does not care about the value contained in the -- constructor: -- --- >>> import GHC.Internal.Control.Monad ( when ) +-- >>> import Control.Monad ( when ) -- >>> let report e = when (isRight e) $ putStrLn "SUCCESS" -- >>> report (Left "parse error") -- >>> report (Right 1) diff --git a/libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs b/libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs index 32a443a771de..079e214d9d51 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs @@ -48,60 +48,6 @@ module GHC.Internal.Data.Foldable ( -- * Searches notElem, find - - -- * Overview - -- $overview - - -- ** Expectation of efficient left-to-right iteration - -- $chirality - - -- ** Recursive and corecursive reduction - -- $reduction - - -- *** Strict recursive folds - -- $strict - - -- **** List of strict functions - -- $strictlist - - -- *** Lazy corecursive folds - -- $lazy - - -- **** List of lazy functions - -- $lazylist - - -- *** Short-circuit folds - -- $shortcircuit - - -- **** List of short-circuit functions - -- $shortlist - - -- *** Hybrid folds - -- $hybrid - - -- ** Generative Recursion - -- $generative - - -- ** Avoiding multi-pass folds - -- $multipass - - -- * Defining instances - -- $instances - - -- *** Being strict by being lazy - -- $strictlazy - - -- * Laws - -- $laws - - -- * Notes - -- $notes - - -- ** Generally linear-time `elem` - -- $linear - - -- * See also - -- $also ) where import GHC.Internal.Data.Bool @@ -237,9 +183,9 @@ class Foldable t where -- strictly compute the `xor` of a list of 'Int' values. -- -- >>> :set -XGeneralizedNewtypeDeriving - -- >>> import GHC.Internal.Data.Bits (Bits, FiniteBits, xor, zeroBits) - -- >>> import GHC.Internal.Data.Foldable (foldMap') - -- >>> import GHC.Internal.Numeric (showHex) + -- >>> import Data.Bits (Bits, FiniteBits, xor, zeroBits) + -- >>> import Data.Foldable (foldMap') + -- >>> import Numeric (showHex) -- >>> -- >>> newtype X a = X a deriving (Eq, Bounded, Enum, Bits, FiniteBits) -- >>> instance Bits a => Semigroup (X a) where X a <> X b = X (a `xor` b) @@ -963,7 +909,7 @@ deriving instance Foldable UInt -- | @since base-4.9.0.0 deriving instance Foldable UWord --- Instances for GHC.Internal.Data.Ord +-- Instances for Data.Ord -- | @since base-4.12.0.0 deriving instance Foldable Down @@ -1082,7 +1028,7 @@ foldlM f z0 xs = foldr c return xs z0 -- | Map each element of a structure to an 'Applicative' action, evaluate these -- actions from left to right, and ignore the results. For a version that --- doesn't ignore the results see 'GHC.Internal.Data.Traversable.traverse'. +-- doesn't ignore the results see 'Data.Traversable.traverse'. -- -- 'traverse_' is just like 'mapM_', but generalised to 'Applicative' actions. -- @@ -1101,7 +1047,7 @@ traverse_ f = foldr c (pure ()) {-# INLINE c #-} -- | 'for_' is 'traverse_' with its arguments flipped. For a version --- that doesn't ignore the results see 'GHC.Internal.Data.Traversable.for'. This +-- that doesn't ignore the results see 'Data.Traversable.for'. This -- is 'forM_' generalised to 'Applicative' actions. -- -- 'for_' is just like 'forM_', but generalised to 'Applicative' actions. @@ -1122,7 +1068,7 @@ for_ = flip traverse_ -- | Map each element of a structure to a monadic action, evaluate -- these actions from left to right, and ignore the results. For a -- version that doesn't ignore the results see --- 'GHC.Internal.Data.Traversable.mapM'. +-- 'Data.Traversable.mapM'. -- -- 'mapM_' is just like 'traverse_', but specialised to monadic actions. -- @@ -1133,7 +1079,7 @@ mapM_ f = foldr c (return ()) {-# INLINE c #-} -- | 'forM_' is 'mapM_' with its arguments flipped. For a version that --- doesn't ignore the results see 'GHC.Internal.Data.Traversable.forM'. +-- doesn't ignore the results see 'Data.Traversable.forM'. -- -- 'forM_' is just like 'for_', but specialised to monadic actions. -- @@ -1143,7 +1089,7 @@ forM_ = flip mapM_ -- | Evaluate each action in the structure from left to right, and -- ignore the results. For a version that doesn't ignore the results --- see 'GHC.Internal.Data.Traversable.sequenceA'. +-- see 'Data.Traversable.sequenceA'. -- -- 'sequenceA_' is just like 'sequence_', but generalised to 'Applicative' -- actions. @@ -1164,7 +1110,7 @@ sequenceA_ = foldr c (pure ()) -- | Evaluate each monadic action in the structure from left to right, -- and ignore the results. For a version that doesn't ignore the --- results see 'GHC.Internal.Data.Traversable.sequence'. +-- results see 'Data.Traversable.sequence'. -- -- 'sequence_' is just like 'sequenceA_', but specialised to monadic -- actions. @@ -1570,1018 +1516,3 @@ the number of elements combined). The `mconcat` implementations for `Text` and elements in a single pass. -} --------------- - --- $overview --- --- #overview# --- The Foldable class generalises some common "Data.List" functions to --- structures that can be reduced to a summary value one element at a time. --- --- == Left and right folds --- --- #leftright# --- The contribution of each element to the final result is combined with an --- accumulator via a suitable /operator/. The operator may be explicitly --- provided by the caller as with `foldr` or may be implicit as in `length`. --- In the case of `foldMap`, the caller provides a function mapping each --- element into a suitable 'Monoid', which makes it possible to merge the --- per-element contributions via that monoid's `mappend` function. --- --- A key distinction is between left-associative and right-associative --- folds: --- --- * In left-associative folds the accumulator is a partial fold over the --- elements that __precede__ the current element, and is passed to the --- operator as its first (left) argument. The outermost application of the --- operator merges the contribution of the last element of the structure with --- the contributions of all its predecessors. --- --- * In right-associative folds the accumulator is a partial fold over the --- elements that __follow__ the current element, and is passed to the --- operator as its second (right) argument. The outermost application of --- the operator merges the contribution of the first element of the structure --- with the contributions of all its successors. --- --- These two types of folds are typified by the left-associative strict --- 'foldl'' and the right-associative lazy `foldr`. --- --- @ --- 'foldl'' :: Foldable t => (b -> a -> b) -> b -> t a -> b --- `foldr` :: Foldable t => (a -> b -> b) -> b -> t a -> b --- @ --- --- Example usage: --- --- >>> foldl' (+) 0 [1..100] --- 5050 --- >>> foldr (&&) True (repeat False) --- False --- --- The first argument of both is an explicit /operator/ that merges the --- contribution of an element of the structure with a partial fold over, --- respectively, either the preceding or following elements of the structure. --- --- The second argument of both is an initial accumulator value @z@ of type --- @b@. This is the result of the fold when the structure is empty. --- When the structure is non-empty, this is the accumulator value merged with --- the first element in left-associative folds, or with the last element in --- right-associative folds. --- --- The third and final argument is a @Foldable@ structure containing elements --- @(a, b, c, …)@. --- --- * __'foldl''__ takes an operator argument of the form: --- --- @ --- f :: b -- accumulated fold of the initial elements --- -> a -- current element --- -> b -- updated fold, inclusive of current element --- @ --- --- If the structure's last element is @y@, the result of the fold is: --- --- @ --- g y . … . g c . g b . g a $ z --- where g element !acc = f acc element --- @ --- --- Since 'foldl'' is strict in the accumulator, this is always --- a [strict](#strict) reduction with no opportunity for early return or --- intermediate results. The structure must be finite, since no result is --- returned until the last element is processed. The advantage of --- strictness is space efficiency: the final result can be computed without --- storing a potentially deep stack of lazy intermediate results. --- --- * __`foldr`__ takes an operator argument of the form: --- --- @ --- f :: a -- current element --- -> b -- accumulated fold of the remaining elements --- -> b -- updated fold, inclusive of current element --- @ --- --- the result of the fold is: --- --- @f a . f b . f c . … $ z@ --- --- If each call of @f@ on the current element @e@, (referenced as @(f e)@ --- below) returns a structure in which its second argument is captured in a --- lazily-evaluated component, then the fold of the remaining elements is --- available to the caller of `foldr` as a pending computation (thunk) that --- is computed only when that component is evaluated. --- --- Alternatively, if any of the @(f e)@ ignore their second argument, the --- fold stops there, with the remaining elements unused. As a result, --- `foldr` is well suited to define both [corecursive](#corec) --- and [short-circuit](#short) reductions. --- --- When the operator is always strict in its second argument, 'foldl'' is --- generally a better choice than `foldr`. When `foldr` is called with a --- strict operator, evaluation cannot begin until the last element is --- reached, by which point a deep stack of pending function applications --- may have been built up in memory. --- - --- $chirality --- --- #chirality# --- Foldable structures are generally expected to be efficiently iterable from --- left to right. Right-to-left iteration may be substantially more costly, or --- even impossible (as with, for example, infinite lists). The text in the --- sections that follow that suggests performance differences between --- left-associative and right-associative folds assumes /left-handed/ --- structures in which left-to-right iteration is cheaper than right-to-left --- iteration. --- --- In finite structures for which right-to-left sequencing no less efficient --- than left-to-right sequencing, there is no inherent performance distinction --- between left-associative and right-associative folds. If the structure's --- @Foldable@ instance takes advantage of this symmetry to also make strict --- right folds space-efficient and lazy left folds corecursive, one need only --- take care to choose either a strict or lazy method for the task at hand. --- --- Foldable instances for symmetric structures should strive to provide equally --- performant left-associative and right-associative interfaces. The main --- limitations are: --- --- * The lazy 'fold', 'foldMap' and 'toList' methods have no right-associative --- counterparts. --- * The strict 'foldMap'' method has no left-associative counterpart. --- --- Thus, for some foldable structures 'foldr'' is just as efficient as 'foldl'' --- for strict reduction, and 'foldl' may be just as appropriate for corecursive --- folds as 'foldr'. --- --- Finally, in some less common structures (e.g. /snoc/ lists) right to left --- iterations are cheaper than left to right. Such structures are poor --- candidates for a @Foldable@ instance, and are perhaps best handled via their --- type-specific interfaces. If nevertheless a @Foldable@ instance is --- provided, the material in the sections that follow applies to these also, by --- replacing each method with one with the opposite associativity (when --- available) and switching the order of arguments in the fold's /operator/. --- --- You may need to pay careful attention to strictness of the fold's /operator/ --- when its strictness is different between its first and second argument. --- For example, while @('+')@ is expected to be commutative and strict in both --- arguments, the list concatenation operator @('++')@ is not commutative and --- is only strict in the initial constructor of its first argument. The fold: --- --- > myconcat xs = foldr (\a b -> a ++ b) [] xs --- --- is substantially cheaper (linear in the length of the consumed portion of --- the final list, thus e.g. constant time/space for just the first element) --- than: --- --- > revconcat xs = foldr (\a b -> b ++ a) [] xs --- --- In which the total cost scales up with both the number of lists combined and --- the number of elements ultimately consumed. A more efficient way to combine --- lists in reverse order, is to use: --- --- > revconcat = foldr (++) [] . reverse - --------------- - --- $reduction --- --- As observed in the [above description](#leftright) of left and right folds, --- there are three general ways in which a structure can be reduced to a --- summary value: --- --- * __Recursive__ reduction, which is strict in all the elements of the --- structure. This produces a single final result only after processing the --- entire input structure, and so the input must be finite. --- --- * __Corecursion__, which yields intermediate results as it encounters --- additional input elements. Lazy processing of the remaining elements --- makes the intermediate results available even before the rest of the --- input is processed. The input may be unbounded, and the caller can --- stop processing intermediate results early. --- --- * __Short-circuit__ reduction, which examines some initial sequence of the --- input elements, but stops once a termination condition is met, returning a --- final result based only on the elements considered up to that point. The --- remaining elements are not considered. The input should generally be --- finite, because the termination condition might otherwise never be met. --- --- Whether a fold is recursive, corecursive or short-circuiting can depend on --- both the method chosen to perform the fold and on the operator passed to --- that method (which may be implicit, as with the `mappend` method of a monoid --- instance). --- --- There are also hybrid cases, where the method and/or operator are not well --- suited to the task at hand, resulting in a fold that fails to yield --- incremental results until the entire input is processed, or fails to --- strictly evaluate results as it goes, deferring all the work to the --- evaluation of a large final thunk. Such cases should be avoided, either by --- selecting a more appropriate @Foldable@ method, or by tailoring the operator --- to the chosen method. --- --- The distinction between these types of folds is critical, both in deciding --- which @Foldable@ method to use to perform the reduction efficiently, and in --- writing @Foldable@ instances for new structures. Below is a more detailed --- overview of each type. - --------------- - --- $strict --- #strict# --- --- Common examples of strict recursive reduction are the various /aggregate/ --- functions, like 'sum', 'product', 'length', as well as more complex --- summaries such as frequency counts. These functions return only a single --- value after processing the entire input structure. In such cases, lazy --- processing of the tail of the input structure is generally not only --- unnecessary, but also inefficient. Thus, these and similar folds should be --- implemented in terms of strict left-associative @Foldable@ methods (typically --- 'foldl'') to perform an efficient reduction in constant space. --- --- Conversely, an implementation of @Foldable@ for a new structure should --- ensure that 'foldl'' actually performs a strict left-associative reduction. --- --- The 'foldMap'' method is a special case of 'foldl'', in which the initial --- accumulator is `mempty` and the operator is @mappend . f@, where @f@ maps --- each input element into the 'Monoid' in question. Therefore, 'foldMap'' is --- an appropriate choice under essentially the same conditions as 'foldl'', and --- its implementation for a given @Foldable@ structure should also be a strict --- left-associative reduction. --- --- While the examples below are not necessarily the most optimal definitions of --- the intended functions, they are all cases in which 'foldMap'' is far more --- appropriate (as well as more efficient) than the lazy `foldMap`. --- --- > length = getSum . foldMap' (const (Sum 1)) --- > sum = getSum . foldMap' Sum --- > product = getProduct . foldMap' Product --- --- [ The actual default definitions employ coercions to optimise out --- 'getSum' and 'getProduct'. ] - --------------- - --- $strictlist --- --- The full list of strict recursive functions in this module is: --- --- * Provided the operator is strict in its left argument: --- --- @'foldl'' :: Foldable t => (b -> a -> b) -> b -> t a -> b@ --- --- * Provided `mappend` is strict in its left argument: --- --- @'foldMap'' :: (Foldable t, Monoid m) => (a -> m) -> t a -> m@ --- --- * Provided the instance is correctly defined: --- --- @ --- `length` :: Foldable t => t a -> Int --- `sum` :: (Foldable t, Num a) => t a -> a --- `product` :: (Foldable t, Num a) => t a -> a --- `maximum` :: (Foldable t, Ord a) => t a -> a --- `minimum` :: (Foldable t, Ord a) => t a -> a --- `maximumBy` :: Foldable t => (a -> a -> Ordering) -> t a -> a --- `minimumBy` :: Foldable t => (a -> a -> Ordering) -> t a -> a --- @ - --------------- - --- $lazy --- --- #corec# --- Common examples of lazy corecursive reduction are functions that map and --- flatten a structure to a lazy stream of result values, i.e. an iterator --- over the transformed input elements. In such cases, it is important to --- choose a @Foldable@ method that is lazy in the tail of the structure, such --- as `foldr` (or `foldMap`, if the result @Monoid@ has a lazy `mappend` as --- with e.g. ByteString Builders). --- --- Conversely, an implementation of `foldr` for a structure that can --- accommodate a large (and possibly unbounded) number of elements is expected --- to be lazy in the tail of the input, allowing operators that are lazy in the --- accumulator to yield intermediate results incrementally. Such folds are --- right-associative, with the tail of the stream returned as a lazily --- evaluated component of the result (an element of a tuple or some other --- non-strict constructor, e.g. the @(:)@ constructor for lists). --- --- The @toList@ function below lazily transforms a @Foldable@ structure to a --- List. Note that this transformation may be lossy, e.g. for a keyed --- container (@Map@, @HashMap@, …) the output stream holds only the --- values, not the keys. Lossless transformations to\/from lists of @(key, --- value)@ pairs are typically available in the modules for the specific --- container types. --- --- > toList = foldr (:) [] --- --- A more complex example is concatenation of a list of lists expressed as a --- nested right fold (bypassing @('++')@). We can check that the definition is --- indeed lazy by folding an infinite list of lists, and taking an initial --- segment. --- --- >>> myconcat = foldr (\x z -> foldr (:) z x) [] --- >>> take 15 $ myconcat $ map (\i -> [0..i]) [0..] --- [0,0,1,0,1,2,0,1,2,3,0,1,2,3,4] --- --- Of course in this case another way to achieve the same result is via a --- list comprehension: --- --- > myconcat xss = [x | xs <- xss, x <- xs] - --------------- - --- $lazylist --- --- The full list of lazy corecursive functions in this module is: --- --- * Provided the reduction function is lazy in its second argument, --- (otherwise best to use a strict recursive reduction): --- --- @ --- `foldr` :: Foldable t => (a -> b -> b) -> b -> t a -> b --- `foldr1` :: Foldable t => (a -> a -> a) -> t a -> a --- @ --- --- * Provided the 'Monoid' `mappend` is lazy in its second argument --- (otherwise best to use a strict recursive reduction): --- --- @ --- `fold` :: Foldable t => Monoid m => t m -> m --- `foldMap` :: Foldable t => Monoid m => (a -> m) -> t a -> m --- @ --- --- * Provided the instance is correctly defined: --- --- @ --- `toList` :: Foldable t => t a -> [a] --- `concat` :: Foldable t => t [a] -> [a] --- `concatMap` :: Foldable t => (a -> [b]) -> t a -> [b] --- @ - --------------- - --- $shortcircuit --- --- #short# --- Examples of short-circuit reduction include various boolean predicates that --- test whether some or all the elements of a structure satisfy a given --- condition. Because these don't necessarily consume the entire list, they --- typically employ `foldr` with an operator that is conditionally strict in --- its second argument. Once the termination condition is met the second --- argument (tail of the input structure) is ignored. No result is returned --- until that happens. --- --- The key distinguishing feature of these folds is /conditional/ strictness --- in the second argument, it is sometimes evaluated and sometimes not. --- --- The simplest (degenerate case) of these is 'null', which determines whether --- a structure is empty or not. This only needs to look at the first element, --- and only to the extent of whether it exists or not, and not its value. In --- this case termination is guaranteed, and infinite input structures are fine. --- Its default definition is of course in terms of the lazy 'foldr': --- --- > null = foldr (\_ _ -> False) True --- --- A more general example is `any`, which applies a predicate to each input --- element in turn until it finds the first one for which the predicate is --- true, at which point it returns success. If, in an infinite input stream --- the predicate is false for all the elements, `any` will not terminate, --- but since it runs in constant space, it typically won't run out of memory, --- it'll just loop forever. - --------------- - --- $shortlist --- --- The full list of short-circuit folds in this module is: --- --- * Boolean predicate folds. --- These functions examine elements strictly until a condition is met, --- but then return a result ignoring the rest (lazy in the tail). These --- may loop forever given an unbounded input where no elements satisfy the --- termination condition. --- --- @ --- `null` :: Foldable t => t a -> Bool --- `elem` :: Foldable t => Eq a => a -> t a -> Bool --- `notElem` :: (Foldable t, Eq a) => a -> t a -> Bool --- `and` :: Foldable t => t Bool -> Bool --- `or` :: Foldable t => t Bool -> Bool --- `find` :: Foldable t => (a -> Bool) -> t a -> Maybe a --- `any` :: Foldable t => (a -> Bool) -> t a -> Bool --- `all` :: Foldable t => (a -> Bool) -> t a -> Bool --- @ --- --- * Many instances of @('<|>')@ (e.g. the 'Maybe' instance) are conditionally --- lazy, and use or don't use their second argument depending on the value --- of the first. These are used with the folds below, which terminate as --- early as possible, but otherwise generally keep going. Some instances --- (e.g. for List) are always strict, but the result is lazy in the tail --- of the output, so that `asum` for a list of lists is in fact corecursive. --- These folds are defined in terms of `foldr`. --- --- @ --- `asum` :: (Foldable t, Alternative f) => t (f a) -> f a --- `msum` :: (Foldable t, MonadPlus m) => t (m a) -> m a --- @ --- --- * Likewise, the @('*>')@ operator in some `Applicative` functors, and @('>>')@ --- in some monads are conditionally lazy and can /short-circuit/ a chain of --- computations. The below folds will terminate as early as possible, but --- even infinite loops can be productive here, when evaluated solely for --- their stream of IO side-effects. See "Data.Traversable#effectful" --- for discussion of related functions. --- --- @ --- `traverse_` :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () --- `for_` :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () --- `sequenceA_` :: (Foldable t, Applicative f) => t (f a) -> f () --- `mapM_` :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () --- `forM_` :: (Foldable t, Monad m) => t a -> (a -> m b) -> m () --- `sequence_` :: (Foldable t, Monad m) => t (m a) -> m () --- @ --- --- * Finally, there's one more special case, `foldlM`: --- --- @`foldlM` :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b@ --- --- The sequencing of monadic effects proceeds from left to right. If at --- some step the bind operator @('>>=')@ short-circuits (as with, e.g., --- 'mzero' with a 'MonadPlus', or an exception with a 'MonadThrow', etc.), --- then the evaluated effects will be from an initial portion of the --- element sequence. --- --- >>> :set -XBangPatterns --- >>> import GHC.Internal.Control.Monad --- >>> import Control.Monad.Trans.Class --- >>> import Control.Monad.Trans.Maybe --- >>> import GHC.Internal.Data.Foldable --- >>> let f !_ e = when (e > 3) mzero >> lift (print e) --- >>> runMaybeT $ foldlM f () [0..] --- 0 --- 1 --- 2 --- 3 --- Nothing --- --- Contrast this with `foldrM`, which sequences monadic effects from right --- to left, and therefore diverges when folding an unbounded input --- structure without ever having the opportunity to short-circuit. --- --- >>> let f e _ = when (e > 3) mzero >> lift (print e) --- >>> runMaybeT $ foldrM f () [0..] --- ...hangs... --- --- When the structure is finite `foldrM` performs the monadic effects from --- right to left, possibly short-circuiting after processing a tail portion --- of the element sequence. --- --- >>> let f e _ = when (e < 3) mzero >> lift (print e) --- >>> runMaybeT $ foldrM f () [0..5] --- 5 --- 4 --- 3 --- Nothing - --------------- - --- $hybrid --- --- The below folds, are neither strict reductions that produce a final answer --- in constant space, nor lazy corecursions, and so have limited applicability. --- They do have specialised uses, but are best avoided when in doubt. --- --- @ --- 'foldr'' :: Foldable t => (a -> b -> b) -> b -> t a -> b --- 'foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b --- 'foldl1' :: Foldable t => (a -> a -> a) -> t a -> a --- 'foldrM' :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b --- @ --- --- The lazy left-folds (used corecursively) and 'foldrM' (used to sequence --- actions right-to-left) can be performant in structures whose @Foldable@ --- instances take advantage of efficient right-to-left iteration to compute --- lazy left folds outside-in from the rightmost element. --- --- The strict 'foldr'' is the least likely to be useful, structures that --- support efficient sequencing /only/ right-to-left are not common. - --------------- - --- $instances --- --- #instances# --- For many structures reasonably efficient @Foldable@ instances can be derived --- automatically, by enabling the @DeriveFoldable@ GHC extension. When this --- works, it is generally not necessary to define a custom instance by hand. --- Though in some cases one may be able to get slightly faster hand-tuned code, --- care is required to avoid producing slower code, or code that is not --- sufficiently lazy, strict or /lawful/. --- --- The hand-crafted instances can get away with only defining one of 'foldr' or --- 'foldMap'. All the other methods have default definitions in terms of one --- of these. The default definitions have the expected strictness and the --- expected asymptotic runtime and space costs, modulo small constant factors. --- If you choose to hand-tune, benchmarking is advised to see whether you're --- doing better than the default derived implementations, plus careful tests to --- ensure that the custom methods are correct. --- --- Below we construct a @Foldable@ instance for a data type representing a --- (finite) binary tree with depth-first traversal. --- --- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) --- --- a suitable instance would be: --- --- > instance Foldable Tree where --- > foldr f z Empty = z --- > foldr f z (Leaf x) = f x z --- > foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l --- --- The 'Node' case is a right fold of the left subtree whose initial --- value is a right fold of the rest of the tree. --- --- For example, when @f@ is @(':')@, all three cases return an immediate value, --- respectively @z@ or a /cons cell/ holding @x@ or @l@, with the remainder the --- structure, if any, encapsulated in a lazy thunk. This meets the expected --- efficient [corecursive](#corec) behaviour of 'foldr'. --- --- Alternatively, one could define @foldMap@: --- --- > instance Foldable Tree where --- > foldMap f Empty = mempty --- > foldMap f (Leaf x) = f x --- > foldMap f (Node l k r) = foldMap f l <> f k <> foldMap f r --- --- And indeed some efficiency may be gained by directly defining both, --- avoiding some indirection in the default definitions that express --- one in terms of the other. If you implement just one, likely 'foldr' --- is the better choice. --- --- A binary tree typically (when balanced, or randomly biased) provides equally --- efficient access to its left and right subtrees. This makes it possible to --- define a `foldl` optimised for [corecursive](#corec) folds with operators --- that are lazy in their first (left) argument. --- --- > instance Foldable Tree where --- > foldr f z Empty = z --- > foldr f z (Leaf x) = f x z --- > foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l --- > -- --- > foldMap f Empty = mempty --- > foldMap f (Leaf x) = f x --- > foldMap f (Node l k r) = foldMap f l <> f k <> foldMap f r --- > -- --- > foldl f z Empty = z --- > foldl f z (Leaf x) = f z x --- > foldl f z (Node l k r) = foldl f (f (foldl f z l) k) r --- --- Now left-to-right and right-to-left iteration over the structure --- elements are equally efficient (note the mirror-order output when --- using `foldl`): --- --- >>> foldr (\e acc -> e : acc) [] (Node (Leaf 1) 2 (Leaf 3)) --- [1,2,3] --- >>> foldl (\acc e -> e : acc) [] (Node (Leaf 1) 2 (Leaf 3)) --- [3,2,1] --- --- We can carry this further, and define more non-default methods... --- --- The structure definition actually admits trees that are unbounded on either --- or both sides. The only fold that can plausibly terminate for a tree --- unbounded on both left and right is `null`, when defined as shown below. --- The default definition in terms of `foldr` diverges if the tree is unbounded --- on the left. Here we define a variant that avoids travelling down the tree --- to find the leftmost element and just examines the root node. --- --- > null Empty = True --- > null _ = False --- --- This is a sound choice also for finite trees. --- --- In practice, unbounded trees are quite uncommon, and can barely be said to --- be @Foldable@. They would typically employ breadth first traversal, and --- would support only corecursive and short-circuit folds (diverge under strict --- reduction). --- --- Returning to simpler instances, defined just in terms of `foldr`, it is --- somewhat surprising that a fairly efficient /default/ implementation of the --- strict 'foldl'' is defined in terms of lazy `foldr` when only the latter is --- explicitly provided by the instance. It may be instructive to take a look --- at how this works. - --------------- - --- $strictlazy --- --- #strictlazy# --- --- Sometimes, it is useful for the result of applying 'foldr' to be a --- /function/. This is done by mapping the structure elements to functions --- with the same argument and result types. The per-element functions are then --- composed to give the final result. --- --- For example, we can /flip/ the strict left fold 'foldl'' by writing: --- --- > foldl' f z xs = flippedFoldl' f xs z --- --- with the function 'flippedFoldl'' defined as below, with 'seq' used to --- ensure the strictness in the accumulator: --- --- > flippedFoldl' f [] z = z --- > flippedFoldl' f (x : xs) z = z `seq` flippedFoldl' f xs (f z x) --- --- Rewriting to use lambdas, this is: --- --- > flippedFoldl' f [] = \ b -> b --- > flippedFoldl' f (x : xs) = \ b -> b `seq` r (f b x) --- > where r = flippedFoldl' f xs --- --- The above has the form of a right fold, enabling a rewrite to: --- --- > flippedFoldl' f = \ xs -> foldr f' id xs --- > where f' x r = \ b -> b `seq` r (f b x) --- --- We can now unflip this to get 'foldl'': --- --- > foldl' f z = \ xs -> foldr f' id xs z --- > -- \ xs -> flippedFoldl' f xs z --- > where f' x r = \ b -> b `seq` r (f b x) --- --- The function __@foldr f' id xs@__ applied to @z@ is built corecursively, and --- its terms are applied to an eagerly evaluated accumulator before further --- terms are applied to the result. As required, this runs in constant space, --- and can be optimised to an efficient loop. --- --- (The actual definition of 'foldl'' labels the lambdas in the definition of --- __@f'@__ above as /oneShot/, which enables further optimisations). - --------------- - --- $generative --- --- #generative# --- So far, we have not discussed /generative recursion/. Unlike recursive --- reduction or corecursion, instead of processing a sequence of elements --- already in memory, generative recursion involves producing a possibly --- unbounded sequence of values from an initial seed value. The canonical --- example of this is 'GHC.Internal.Data.List.unfoldr' for Lists, with variants available --- for Vectors and various other structures. --- --- A key issue with lists, when used generatively as /iterators/, rather than as --- poor-man's containers (see [[1\]](#uselistsnot)), is that such iterators --- tend to consume memory when used more than once. A single traversal of a --- list-as-iterator will run in constant space, but as soon as the list is --- retained for reuse, its entire element sequence is stored in memory, and the --- second traversal reads the copy, rather than regenerates the elements. It --- is sometimes better to recompute the elements rather than memoise the list. --- --- Memoisation happens because the built-in Haskell list __@[]@__ is --- represented as __data__, either empty or a /cons-cell/ holding the first --- element and the tail of the list. The @Foldable@ class enables a variant --- representation of iterators as /functions/, which take an operator and a --- starting accumulator and output a summary result. --- --- The [@fmlist@](https://hackage.haskell.org/package/fmlist) package takes --- this approach, by representing a list via its `foldMap` action. --- --- Below we implement an analogous data structure using a representation --- based on `foldr`. This is an example of /Church encoding/ --- (named after Alonzo Church, inventor of the lambda calculus). --- --- > {-# LANGUAGE RankNTypes #-} --- > newtype FRList a = FR { unFR :: forall b. (a -> b -> b) -> b -> b } --- --- The __@unFR@__ field of this type is essentially its `foldr` method --- with the list as its first rather than last argument. Thus we --- immediately get a @Foldable@ instance (and a 'toList' function --- mapping an __@FRList@__ to a regular list). --- --- > instance Foldable FRList where --- > foldr f z l = unFR l f z --- > -- With older versions of @base@, also define sum, product, ... --- > -- to ensure use of the strict 'foldl''. --- > -- sum = foldl' (+) 0 --- > -- ... --- --- We can convert a regular list to an __@FRList@__ with: --- --- > fromList :: [a] -> FRList a --- > fromList as = FRList $ \ f z -> foldr f z as --- --- However, reuse of an __@FRList@__ obtained in this way will typically --- memoise the underlying element sequence. Instead, we can define --- __@FRList@__ terms directly: --- --- > -- | Immediately return the initial accumulator --- > nil :: FRList a --- > nil = FRList $ \ _ z -> z --- > {-# INLINE nil #-} --- --- > -- | Fold the tail to use as an accumulator with the new initial element --- > cons :: a -> FRList a -> FRList a --- > cons a l = FRList $ \ f z -> f a (unFR l f z) --- > {-# INLINE cons #-} --- --- More crucially, we can also directly define the key building block for --- generative recursion: --- --- > -- | Generative recursion, dual to `foldr`. --- > unfoldr :: (s -> Maybe (a, s)) -> s -> FRList a --- > unfoldr g s0 = FR generate --- > where generate f z = loop s0 --- > where loop s | Just (a, t) <- g s = f a (loop t) --- > | otherwise = z --- > {-# INLINE unfoldr #-} --- --- Which can, for example, be specialised to number ranges: --- --- > -- | Generate a range of consecutive integral values. --- > range :: (Ord a, Integral a) => a -> a -> FRList a --- > range lo hi = --- > unfoldr (\s -> if s > hi then Nothing else Just (s, s+1)) lo --- > {-# INLINE range #-} --- --- The program below, when compiled with optimisation: --- --- > main :: IO () --- > main = do --- > let r :: FRList Int --- > r = range 1 10000000 --- > in print (sum r, length r) --- --- produces the expected output with no noticeable garbage-collection, despite --- reuse of the __@FRList@__ term __@r@__. --- --- > (50000005000000,10000000) --- > 52,120 bytes allocated in the heap --- > 3,320 bytes copied during GC --- > 44,376 bytes maximum residency (1 sample(s)) --- > 25,256 bytes maximum slop --- > 3 MiB total memory in use (0 MB lost due to fragmentation) --- --- The Weak Head Normal Form of an __@FRList@__ is a lambda abstraction not a --- data value, and reuse does not lead to memoisation. Reuse of the iterator --- above is somewhat contrived, when computing multiple folds over a common --- list, you should generally traverse a list only [once](#multipass). The --- goal is to demonstrate that the separate computations of the 'sum' and --- 'length' run efficiently in constant space, despite reuse. This would not --- be the case with the list @[1..10000000]@. --- --- This is, however, an artificially simple reduction. More typically, there --- are likely to be some allocations in the inner loop, but the temporary --- storage used will be garbage-collected as needed, and overall memory --- utilisation will remain modest and will not scale with the size of the list. --- --- If we go back to built-in lists (i.e. __@[]@__), but avoid reuse by --- performing reduction in a single pass, as below: --- --- > data PairS a b = P !a !b -- We define a strict pair datatype --- > --- > main :: IO () --- > main = do --- > let l :: [Int] --- > l = [1..10000000] --- > in print $ average l --- > where --- > sumlen :: PairS Int Int -> Int -> PairS Int Int --- > sumlen (P s l) a = P (s + a) (l + 1) --- > --- > average is = --- > let (P s l) = foldl' sumlen (P 0 0) is --- > in (fromIntegral s :: Double) / fromIntegral l --- --- the result is again obtained in constant space: --- --- > 5000000.5 --- > 102,176 bytes allocated in the heap --- > 3,320 bytes copied during GC --- > 44,376 bytes maximum residency (1 sample(s)) --- > 25,256 bytes maximum slop --- > 3 MiB total memory in use (0 MB lost due to fragmentation) --- --- (and, in fact, faster than with __@FRList@__ by a small factor). --- --- The __@[]@__ list structure works as an efficient iterator when used --- just once. When space-leaks via list reuse are not a concern, and/or --- memoisation is actually desirable, the regular list implementation is --- likely to be faster. This is not a suggestion to replace all your uses of --- __@[]@__ with a generative alternative. --- --- The __@FRList@__ type could be further extended with instances of 'Functor', --- 'Applicative', 'Monad', 'Alternative', etc., and could then provide a --- fully-featured list type, optimised for reuse without space-leaks. If, --- however, all that's required is space-efficient, re-use friendly iteration, --- less is perhaps more, and just @Foldable@ may be sufficient. - --------------- - --- $multipass --- --- #multipass# --- In applications where you want to compute a composite function of a --- structure, which requires more than one aggregate as an input, it is --- generally best to compute all the aggregates in a single pass, rather --- than to traverse the same structure repeatedly. --- --- The [@foldl@](http://hackage.haskell.org/package/foldl) package implements a --- robust general framework for dealing with this situation. If you choose to --- to do it yourself, with a bit of care, the simplest cases are not difficult --- to handle directly. You just need to accumulate the individual aggregates --- as __strict__ components of a single data type, and then apply a final --- transformation to it to extract the composite result. For example, --- computing an average requires computing both the 'sum' and the 'length' of a --- (non-empty) structure and dividing the sum by the length: --- --- > import GHC.Internal.Data.Foldable (foldl') --- > --- > data PairS a b = P !a !b -- We define a strict pair datatype --- > --- > -- | Compute sum and length in a single pass, then reduce to the average. --- > average :: (Foldable f, Fractional a) => f a -> a --- > average xs = --- > let sumlen (P s l) a = P (s + a) (l + 1 :: Int) --- > (P s l) = foldl' sumlen (P 0 0) xs --- > in s / fromIntegral l --- --- The above example is somewhat contrived, some structures keep track of their --- length internally, and can return it in /O(1)/ time, so this particular --- recipe for averages is not always the most efficient. In general, composite --- aggregate functions of large structures benefit from single-pass reduction. --- This is especially the case when reuse of a list and memoisation of its --- elements is thereby avoided. - --------------- - --- $laws --- #laws# --- --- The type constructor 'Endo' from "Data.Monoid", associates with each type --- __@b@__ the __@newtype@__-encapsulated type of functions mapping __@b@__ to --- itself. Functions from a type to itself are called /endomorphisms/, hence --- the name /Endo/. The type __@Endo b@__ is a 'Monoid' under function --- composition: --- --- > newtype Endo b = Endo { appEndo :: b -> b } --- > instance Semigroup Endo b where --- > Endo f <> Endo g = Endo (f . g) --- > instance Monoid Endo b where --- > mempty = Endo id --- --- For every 'Monoid' m, we also have a 'Dual' monoid __@Dual m@__ which --- combines elements in the opposite order: --- --- > newtype Dual m = Dual { getDual :: m } --- > instance Semigroup m => Semigroup Dual m where --- > Dual a <> Dual b = Dual (b <> a) --- > instance Monoid m => Monoid Dual m where --- > mempty = Dual mempty --- --- With the above preliminaries out of the way, 'Foldable' instances are --- expected to satisfy the following laws: --- --- The 'foldr' method must be equivalent in value and strictness to replacing --- each element __@a@__ of a 'Foldable' structure with __@Endo (f a)@__, --- composing these via 'foldMap' and applying the result to the base case --- __@z@__: --- --- > foldr f z t = appEndo (foldMap (Endo . f) t ) z --- --- Likewise, the 'foldl' method must be equivalent in value and strictness --- to composing the functions __@flip f a@__ in reverse order and applying --- the result to the base case: --- --- > foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z --- --- When the elements of the structure are taken from a 'Monoid', the --- definition of 'fold' must agree with __@foldMap id@__: --- --- > fold = foldMap id --- --- The 'length' method must agree with a 'foldMap' mapping each element to --- __@Sum 1@__ (The 'Sum' type abstracts numbers as a monoid under addition). --- --- > length = getSum . foldMap (Sum . const 1) --- --- @sum@, @product@, @maximum@, and @minimum@ should all be essentially --- equivalent to @foldMap@ forms, such as --- --- > sum = getSum . foldMap' Sum --- > product = getProduct . foldMap' Product --- --- but are generally more efficient when defined more directly as: --- --- > sum = foldl' (+) 0 --- > product = foldl' (*) 1 --- --- If the 'Foldable' structure has a 'Functor' instance, then for every --- function __@f@__ mapping the elements into a 'Monoid', it should satisfy: --- --- > foldMap f = fold . fmap f --- --- which implies that --- --- > foldMap f . fmap g = foldMap (f . g) --- - --------------- - --- $notes --- --- #notes# --- Since 'Foldable' does not have 'Functor' as a superclass, it is possible to --- define 'Foldable' instances for structures that constrain their element --- types. Therefore, __@Set@__ can be 'Foldable', even though sets keep their --- elements in ascending order. This requires the elements to be comparable, --- which precludes defining a 'Functor' instance for @Set@. --- --- The 'Foldable' class makes it possible to use idioms familiar from the @List@ --- type with container structures that are better suited to the task at hand. --- This supports use of more appropriate 'Foldable' data types, such as @Seq@, --- @Set@, @NonEmpty@, etc., without requiring new idioms (see --- [[1\]](#uselistsnot) for when not to use lists). --- --- The more general methods of the 'Foldable' class are now exported by the --- "Prelude" in place of the original List-specific methods (see the --- [FTP Proposal](https://wiki.haskell.org/Foldable_Traversable_In_Prelude)). --- The List-specific variants are for now still available in "GHC.OldList", but --- that module is intended only as a transitional aid, and may be removed in --- the future. --- --- Surprises can arise from the @Foldable@ instance of the 2-tuple @(a,)@ which --- now behaves as a 1-element @Foldable@ container in its second slot. In --- contexts where a specific monomorphic type is expected, and you want to be --- able to rely on type errors to guide refactoring, it may make sense to --- define and use less-polymorphic variants of some of the @Foldable@ methods. --- --- Below are two examples showing a definition of a reusable less-polymorphic --- 'sum' and a one-off in-line specialisation of 'length': --- --- > {-# LANGUAGE TypeApplications #-} --- > --- > mySum :: Num a => [a] -> a --- > mySum = sum --- > --- > type SlowVector a = [a] --- > slowLength :: SlowVector -> Int --- > slowLength v = length @[] v --- --- In both cases, if the data type to which the function is applied changes --- to something other than a list, the call-site will no longer compile until --- appropriate changes are made. - --- $linear --- --- It is perhaps worth noting that since the __`elem`__ function in the --- 'Foldable' class carries only an __`Eq`__ constraint on the element type, --- search for the presence or absence of an element in the structure generally --- takes /O(n)/ time, even for ordered structures like __@Set@__ that are --- potentially capable of performing the search faster. (The @member@ function --- of the @Set@ module carries an `Ord` constraint, and can perform the search --- in /O(log n)/ time). --- --- An alternative to Foldable's __`elem`__ method is required in order to --- abstract potentially faster than linear search over general container --- structures. This can be achieved by defining an additional type class (e.g. --- @HasMember@ below). Instances of such a type class (that are also --- `Foldable') can employ the `elem` linear search as a last resort, when --- faster search is not supported. --- --- > {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} --- > --- > import qualified Data.Set as Set --- > --- > class Eq a => HasMember t a where --- > member :: a -> t a -> Bool --- > --- > instance Eq a => HasMember [] a where --- > member = elem --- > [...] --- > instance Ord a => HasMember Set.Set a where --- > member = Set.member --- --- The above suggests that 'elem' may be a misfit in the 'Foldable' class. --- Alternative design ideas are solicited on GHC's bug tracker via issue --- [\#20421](https://gitlab.haskell.org/ghc/ghc/-/issues/20421). --- --- Note that some structure-specific optimisations may of course be possible --- directly in the corresponding @Foldable@ instance, e.g. with @Set@ the size --- of the set is known in advance, without iterating to count the elements, and --- its `length` instance takes advantage of this to return the size directly. - --------------- - --- $also --- --- * [1] #uselistsnot# \"When You Should Use Lists in Haskell (Mostly, You Should Not)\", --- by Johannes Waldmann, --- in arxiv.org, Programming Languages (cs.PL), at --- <https://arxiv.org/abs/1808.08329>. --- --- * [2] \"The Essence of the Iterator Pattern\", --- by Jeremy Gibbons and Bruno Oliveira, --- in /Mathematically-Structured Functional Programming/, 2006, online at --- <http://www.cs.ox.ac.uk/people/jeremy.gibbons/publications/#iterator>. --- --- * [3] \"A tutorial on the universality and expressiveness of fold\", --- by Graham Hutton, J\. Functional Programming 9 (4): 355–372, July 1999, --- online at <http://www.cs.nott.ac.uk/~pszgmh/fold.pdf>. diff --git a/libraries/ghc-internal/src/GHC/Internal/Data/IORef.hs b/libraries/ghc-internal/src/GHC/Internal/Data/IORef.hs index 5b1d9524619e..ad68e1161b17 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Data/IORef.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Data/IORef.hs @@ -29,10 +29,6 @@ module GHC.Internal.Data.IORef atomicModifyIORef', atomicWriteIORef, mkWeakIORef, - -- ** Memory Model - - -- $memmodel - ) where import GHC.Internal.Base @@ -137,54 +133,3 @@ atomicWriteIORef ref a = do _ <- atomicSwapIORef ref a pure () -{- $memmodel - #memmodel# - - Most modern CPU achitectures (e.g. x86/64, ARM) have a memory model which allows - threads to reorder reads with earlier writes to different locations, - e.g. see <https://www.intel.com/content/www/us/en/developer/articles/technical/intel-sdm.html the x86/64 architecture manual>, - 8.2.3.4 Loads May Be Reordered with Earlier Stores to Different Locations. - - Because of that, in a concurrent program, 'IORef' operations may appear out-of-order - to another thread. In the following example: - - > import GHC.Internal.Data.IORef - > import GHC.Internal.Control.Monad (unless) - > import Control.Concurrent (forkIO, threadDelay) - > - > maybePrint :: IORef Bool -> IORef Bool -> IO () - > maybePrint myRef yourRef = do - > writeIORef myRef True - > yourVal <- readIORef yourRef - > unless yourVal $ putStrLn "critical section" - > - > main :: IO () - > main = do - > r1 <- newIORef False - > r2 <- newIORef False - > forkIO $ maybePrint r1 r2 - > forkIO $ maybePrint r2 r1 - > threadDelay 1000000 - - it is possible that the string @"critical section"@ is printed - twice, even though there is no interleaving of the operations of the - two threads that allows that outcome. The memory model of x86/64 - allows 'readIORef' to happen before the earlier 'writeIORef'. - - The ARM memory order model is typically even weaker than x86/64, allowing - any reordering of reads and writes as long as they are independent - from the point of view of the current thread. - - The implementation is required to ensure that reordering of memory - operations cannot cause type-correct code to go wrong. In - particular, when inspecting the value read from an 'IORef', the - memory writes that created that value must have occurred from the - point of view of the current thread. - - 'atomicWriteIORef', 'atomicModifyIORef' and 'atomicModifyIORef'' act - as a barrier to reordering. Multiple calls to these functions - occur in strict program order, never taking place ahead of any - earlier (in program order) 'IORef' operations, or after any later - 'IORef' operations. - --} diff --git a/libraries/ghc-internal/src/GHC/Internal/Data/Int.hs b/libraries/ghc-internal/src/GHC/Internal/Data/Int.hs index 9dae155dc889..46aefe1e943e 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Data/Int.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Data/Int.hs @@ -16,40 +16,11 @@ ----------------------------------------------------------------------------- module GHC.Internal.Data.Int - ( - -- * Signed integer types - Int, - Int8, Int16, Int32, Int64, - - -- * Notes - - -- $notes - ) where + ( + -- * Signed integer types + Int, + Int8, Int16, Int32, Int64, + ) where import GHC.Internal.Base ( Int ) import GHC.Internal.Int ( Int8, Int16, Int32, Int64 ) - -{- $notes - -* All arithmetic is performed modulo 2^n, where @n@ is the number of - bits in the type. - -* For coercing between any two integer types, use 'Prelude.fromIntegral', - which is specialized for all the common cases so should be fast - enough. Coercing word types (see "Data.Word") to and from integer - types preserves representation, not sign. - -* The rules that hold for 'Prelude.Enum' instances over a - bounded type such as 'Int' (see the section of the - Haskell report dealing with arithmetic sequences) also hold for the - 'Prelude.Enum' instances over the various - 'Int' types defined here. - -* Right and left shifts by amounts greater than or equal to the width - of the type result in either zero or -1, depending on the sign of - the value being shifted. This is contrary to the behaviour in C, - which is undefined; a common interpretation is to truncate the shift - count to the width of the type, for example @1 \<\< 32 - == 1@ in some C implementations. --} - diff --git a/libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs b/libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs index 745ce7550956..a2d40abb3408 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Data/Traversable.hs @@ -35,62 +35,6 @@ module GHC.Internal.Data.Traversable ( -- * General definitions for superclass methods fmapDefault, foldMapDefault, - - -- * Overview - -- $overview - - -- ** The 'traverse' and 'mapM' methods - -- $traverse - - -- *** Their 'Foldable', just the effects, analogues. - -- $effectful - - -- *** Result multiplicity - -- $multiplicity - - -- ** The 'sequenceA' and 'sequence' methods - -- $sequence - - -- *** Care with default method implementations - -- $seqdefault - - -- *** Monadic short circuits - -- $seqshort - - -- ** Example binary tree instance - -- $tree_instance - - -- *** Pre-order and post-order tree traversal - -- $tree_order - - -- ** Making construction intuitive - -- - -- $construction - - -- * Advanced traversals - -- $advanced - - -- *** Coercion - -- $coercion - - -- ** Identity: the 'fmapDefault' function - -- $identity - - -- ** State: the 'mapAccumL', 'mapAccumR' functions - -- $stateful - - -- ** Const: the 'foldMapDefault' function - -- $phantom - - -- ** ZipList: transposing lists of lists - -- $ziplist - - -- * Laws - -- - -- $laws - - -- * See also - -- $also ) where import GHC.Internal.Data.Coerce @@ -139,7 +83,7 @@ class (Functor t, Foldable t) => Traversable t where -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and collect the results. For a version that ignores - -- the results see 'GHC.Internal.Data.Foldable.traverse_'. + -- the results see 'Data.Foldable.traverse_'. -- -- ==== __Examples__ -- @@ -172,7 +116,7 @@ class (Functor t, Foldable t) => Traversable t where -- | Evaluate each action in the structure from left to right, and -- collect the results. For a version that ignores the results - -- see 'GHC.Internal.Data.Foldable.sequenceA_'. + -- see 'Data.Foldable.sequenceA_'. -- -- ==== __Examples__ -- @@ -203,7 +147,7 @@ class (Functor t, Foldable t) => Traversable t where -- | Map each element of a structure to a monadic action, evaluate -- these actions from left to right, and collect the results. For - -- a version that ignores the results see 'GHC.Internal.Data.Foldable.mapM_'. + -- a version that ignores the results see 'Data.Foldable.mapM_'. -- -- ==== __Examples__ -- @@ -217,7 +161,7 @@ class (Functor t, Foldable t) => Traversable t where -- | Evaluate each monadic action in the structure from left to -- right, and collect the results. For a version that ignores the - -- results see 'GHC.Internal.Data.Foldable.sequence_'. + -- results see 'Data.Foldable.sequence_'. -- -- ==== __Examples__ -- @@ -420,26 +364,26 @@ deriving instance Traversable UInt -- | @since base-4.9.0.0 deriving instance Traversable UWord --- Instance for GHC.Internal.Data.Ord +-- Instance for Data.Ord -- | @since base-4.12.0.0 deriving instance Traversable Down -- general functions -- | 'for' is 'traverse' with its arguments flipped. For a version --- that ignores the results see 'GHC.Internal.Data.Foldable.for_'. +-- that ignores the results see 'Data.Foldable.for_'. for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) {-# INLINE for #-} for = flip traverse -- | 'forM' is 'mapM' with its arguments flipped. For a version that --- ignores the results see 'GHC.Internal.Data.Foldable.forM_'. +-- ignores the results see 'Data.Foldable.forM_'. forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) {-# INLINE forM #-} forM = flip mapM -- |The 'mapAccumL' function behaves like a combination of 'fmap' --- and 'GHC.Internal.Data.Foldable.foldl'; it applies a function to each element of a structure, +-- and 'Data.Foldable.foldl'; it applies a function to each element of a structure, -- passing an accumulating parameter from left to right, and returning -- a final value of this accumulator together with the new structure. -- @@ -459,7 +403,7 @@ mapAccumL :: forall t s a b. Traversable t mapAccumL f s t = coerce (traverse @t @(StateL s) @a @b) (flip f) t s -- |The 'mapAccumR' function behaves like a combination of 'fmap' --- and 'GHC.Internal.Data.Foldable.foldr'; it applies a function to each element of a structure, +-- and 'Data.Foldable.foldr'; it applies a function to each element of a structure, -- passing an accumulating parameter from right to left, and returning -- a final value of this accumulator together with the new structure. -- @@ -531,7 +475,7 @@ fmapDefault :: forall t a b . Traversable t -- See Note [Function coercion] in Data.Functor.Utils. fmapDefault = coerce (traverse @t @Identity @a @b) --- | This function may be used as a value for `GHC.Internal.Data.Foldable.foldMap` +-- | This function may be used as a value for `Data.Foldable.foldMap` -- in a `Foldable` instance. -- -- @ @@ -543,1020 +487,3 @@ foldMapDefault :: forall t m a . (Traversable t, Monoid m) -- See Note [Function coercion] in Data.Functor.Utils. foldMapDefault = coerce (traverse @t @(Const m) @a @()) ------------------- - --- $overview --- --- #overview# --- Traversable structures support element-wise sequencing of 'Applicative' --- effects (thus also 'Monad' effects) to construct new structures of --- __the same shape__ as the input. --- --- To illustrate what is meant by /same shape/, if the input structure is --- __@[a]@__, each output structure is a list __@[b]@__ of the same length as --- the input. If the input is a __@Tree a@__, each output __@Tree b@__ has the --- same graph of intermediate nodes and leaves. Similarly, if the input is a --- 2-tuple __@(x, a)@__, each output is a 2-tuple __@(x, b)@__, and so forth. --- --- It is in fact possible to decompose a traversable structure __@t a@__ into --- its shape (a.k.a. /spine/) of type __@t ()@__ and its element list --- __@[a]@__. The original structure can be faithfully reconstructed from its --- spine and element list. --- --- The implementation of a @Traversable@ instance for a given structure follows --- naturally from its type; see the [Construction](#construction) section for --- details. --- Instances must satisfy the laws listed in the [Laws section](#laws). --- The diverse uses of @Traversable@ structures result from the many possible --- choices of Applicative effects. --- See the [Advanced Traversals](#advanced) section for some examples. --- --- Every @Traversable@ structure is both a 'Functor' and 'Foldable' because it --- is possible to implement the requisite instances in terms of 'traverse' by --- using 'fmapDefault' for 'fmap' and 'foldMapDefault' for 'foldMap'. Direct --- fine-tuned implementations of these superclass methods can in some cases be --- more efficient. - ------------------- - --- $traverse --- For an 'Applicative' functor __@f@__ and a @Traversable@ functor __@t@__, --- the type signatures of 'traverse' and 'fmap' are rather similar: --- --- > fmap :: (a -> f b) -> t a -> t (f b) --- > traverse :: (a -> f b) -> t a -> f (t b) --- --- The key difference is that 'fmap' produces a structure whose elements (of --- type __@f b@__) are individual effects, while 'traverse' produces an --- aggregate effect yielding structures of type __@t b@__. --- --- For example, when __@f@__ is the __@IO@__ monad, and __@t@__ is __@List@__, --- 'fmap' yields a list of IO actions, whereas 'traverse' constructs an IO --- action that evaluates to a list of the return values of the individual --- actions performed left-to-right. --- --- > traverse :: (a -> IO b) -> [a] -> IO [b] --- --- The 'mapM' function is a specialisation of 'traverse' to the case when --- __@f@__ is a 'Monad'. For monads, 'mapM' is more idiomatic than 'traverse'. --- The two are otherwise generally identical (though 'mapM' may be specifically --- optimised for monads, and could be more efficient than using the more --- general 'traverse'). --- --- > traverse :: (Applicative f, Traversable t) => (a -> f b) -> t a -> f (t b) --- > mapM :: (Monad m, Traversable t) => (a -> m b) -> t a -> m (t b) --- --- When the traversable term is a simple variable or expression, and the --- monadic action to run is a non-trivial do block, it can be more natural to --- write the action last. This idiom is supported by 'for', 'forM', and --- 'forAccumM' which are the flipped versions of 'traverse', 'mapM', and --- 'mapAccumM' respectively. - ------------------- - --- $multiplicity --- --- #multiplicity# --- When 'traverse' or 'mapM' is applied to an empty structure __@ts@__ (one for --- which __@'null' ts@__ is 'True') the return value is __@pure ts@__ --- regardless of the provided function __@g :: a -> f b@__. It is not possible --- to apply the function when no values of type __@a@__ are available, but its --- type determines the relevant instance of 'pure'. --- --- prop> null ts ==> traverse g ts == pure ts --- --- Otherwise, when __@ts@__ is non-empty and at least one value of type __@b@__ --- results from each __@f a@__, the structures __@t b@__ have /the same shape/ --- (list length, graph of tree nodes, ...) as the input structure __@t a@__, --- but the slots previously occupied by elements of type __@a@__ now hold --- elements of type __@b@__. --- --- A single traversal may produce one, zero or many such structures. The zero --- case happens when one of the effects __@f a@__ sequenced as part of the --- traversal yields no replacement values. Otherwise, the many case happens --- when one of sequenced effects yields multiple values. --- --- The 'traverse' function does not perform selective filtering of slots in the --- output structure as with e.g. 'GHC.Internal.Data.Maybe.mapMaybe'. --- --- >>> let incOdd n = if odd n then Just $ n + 1 else Nothing --- >>> mapMaybe incOdd [1, 2, 3] --- [2,4] --- >>> traverse incOdd [1, 3, 5] --- Just [2,4,6] --- >>> traverse incOdd [1, 2, 3] --- Nothing --- --- In the above examples, with 'Maybe' as the 'Applicative' __@f@__, we see --- that the number of __@t b@__ structures produced by 'traverse' may differ --- from one: it is zero when the result short-circuits to __@Nothing@__. The --- same can happen when __@f@__ is __@List@__ and the result is __@[]@__, or --- __@f@__ is __@Either e@__ and the result is __@Left (x :: e)@__, or perhaps --- the 'Control.Applicative.empty' value of some --- 'Control.Applicative.Alternative' functor. --- --- When __@f@__ is e.g. __@List@__, and the map __@g :: a -> [b]@__ returns --- more than one value for some inputs __@a@__ (and at least one for all --- __@a@__), the result of __@mapM g ts@__ will contain multiple structures of --- the same shape as __@ts@__: --- --- prop> length (mapM g ts) == product (fmap (length . g) ts) --- --- For example: --- --- >>> length $ mapM (\n -> [1..n]) [1..6] --- 720 --- >>> product $ length . (\n -> [1..n]) <$> [1..6] --- 720 --- --- In other words, a traversal with a function __@g :: a -> [b]@__, over an --- input structure __@t a@__, yields a list __@[t b]@__, whose length is the --- product of the lengths of the lists that @g@ returns for each element of the --- input structure! The individual elements __@a@__ of the structure are --- replaced by each element of __@g a@__ in turn: --- --- >>> mapM (\n -> [1..n]) $ Just 3 --- [Just 1,Just 2,Just 3] --- >>> mapM (\n -> [1..n]) [1..3] --- [[1,1,1],[1,1,2],[1,1,3],[1,2,1],[1,2,2],[1,2,3]] --- --- If any element of the structure __@t a@__ is mapped by @g@ to an empty list, --- then the entire aggregate result is empty, because no value is available to --- fill one of the slots of the output structure: --- --- >>> mapM (\n -> [1..n]) $ [0..6] -- [1..0] is empty --- [] - ------------------- - --- $effectful --- #effectful# --- --- The 'traverse' and 'mapM' methods have analogues in the "Data.Foldable" --- module. These are 'traverse_' and 'mapM_', and their flipped variants --- 'for_' and 'forM_', respectively. The result type is __@f ()@__, they don't --- return an updated structure, and can be used to sequence effects over all --- the elements of a @Traversable@ (any 'Foldable') structure just for their --- side-effects. --- --- If the @Traversable@ structure is empty, the result is __@pure ()@__. When --- effects short-circuit, the __@f ()@__ result may, for example, be 'Nothing' --- if __@f@__ is 'Maybe', or __@'Left' e@__ when it is __@'Either' e@__. --- --- It is perhaps worth noting that 'Maybe' is not only a potential --- 'Applicative' functor for the return value of the first argument of --- 'traverse', but is also itself a 'Traversable' structure with either zero or --- one element. A convenient idiom for conditionally executing an action just --- for its effects on a 'Just' value, and doing nothing otherwise is: --- --- > -- action :: Monad m => a -> m () --- > -- mvalue :: Maybe a --- > mapM_ action mvalue -- :: m () --- --- which is more concise than: --- --- > maybe (return ()) action mvalue --- --- The 'mapM_' idiom works verbatim if the type of __@mvalue@__ is later --- refactored from __@Maybe a@__ to __@Either e a@__ (assuming it remains OK to --- silently do nothing in the 'Left' case). - ------------------- - --- $sequence --- --- #sequence# --- The 'sequenceA' and 'sequence' methods are useful when what you have is a --- container of pending applicative or monadic effects, and you want to combine --- them into a single effect that produces zero or more containers with the --- computed values. --- --- > sequenceA :: (Applicative f, Traversable t) => t (f a) -> f (t a) --- > sequence :: (Monad m, Traversable t) => t (m a) -> m (t a) --- > sequenceA = traverse id -- default definition --- > sequence = sequenceA -- default definition --- --- When the monad __@m@__ is 'System.IO.IO', applying 'sequence' to a list of --- IO actions, performs each in turn, returning a list of the results: --- --- > sequence [putStr "Hello ", putStrLn "World!"] --- > = (\a b -> [a,b]) <$> putStr "Hello " <*> putStrLn "World!" --- > = do u1 <- putStr "Hello " --- > u2 <- putStrLn "World!" --- > return [u1, u2] -- In this case [(), ()] --- --- For 'sequenceA', the /non-deterministic/ behaviour of @List@ is most easily --- seen in the case of a list of lists (of elements of some common fixed type). --- The result is a cross-product of all the sublists: --- --- >>> sequenceA [[0, 1, 2], [30, 40], [500]] --- [[0,30,500],[0,40,500],[1,30,500],[1,40,500],[2,30,500],[2,40,500]] --- --- Because the input list has three (sublist) elements, the result is a list of --- triples (/same shape/). - ------------------- - --- $seqshort --- --- #seqshort# --- When the monad __@m@__ is 'Either' or 'Maybe' (more generally any --- 'Control.Monad.MonadPlus'), the effect in question is to short-circuit the --- result on encountering 'Left' or 'Nothing' (more generally --- 'GHC.Internal.Control.Monad.mzero'). --- --- >>> sequence [Just 1,Just 2,Just 3] --- Just [1,2,3] --- >>> sequence [Just 1,Nothing,Just 3] --- Nothing --- >>> sequence [Right 1,Right 2,Right 3] --- Right [1,2,3] --- >>> sequence [Right 1,Left "sorry",Right 3] --- Left "sorry" --- --- The result of 'sequence' is all-or-nothing, either structures of exactly the --- same shape as the input or none at all. The 'sequence' function does not --- perform selective filtering as with e.g. 'GHC.Internal.Data.Maybe.catMaybes' or --- 'GHC.Internal.Data.Either.rights': --- --- >>> catMaybes [Just 1,Nothing,Just 3] --- [1,3] --- >>> rights [Right 1,Left "sorry",Right 3] --- [1,3] - ------------------- - --- $seqdefault --- --- #seqdefault# --- The 'traverse' method has a default implementation in terms of 'sequenceA': --- --- > traverse g = sequenceA . fmap g --- --- but relying on this default implementation is not recommended, it requires --- that the structure is already independently a 'Functor'. The definition of --- 'sequenceA' in terms of __@traverse id@__ is much simpler than 'traverse' --- expressed via a composition of 'sequenceA' and 'fmap'. Instances should --- generally implement 'traverse' explicitly. It may in some cases also make --- sense to implement a specialised 'mapM'. --- --- Because 'fmapDefault' is defined in terms of 'traverse' (whose default --- definition in terms of 'sequenceA' uses 'fmap'), you must not use --- 'fmapDefault' to define the @Functor@ instance if the @Traversable@ instance --- directly defines only 'sequenceA'. - ------------------- - --- $tree_instance --- --- #tree# --- The definition of a 'Traversable' instance for a binary tree is rather --- similar to the corresponding instance of 'Functor', given the data type: --- --- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) --- --- a canonical @Functor@ instance would be --- --- > instance Functor Tree where --- > fmap g Empty = Empty --- > fmap g (Leaf x) = Leaf (g x) --- > fmap g (Node l k r) = Node (fmap g l) (g k) (fmap g r) --- --- a canonical @Traversable@ instance would be --- --- > instance Traversable Tree where --- > traverse g Empty = pure Empty --- > traverse g (Leaf x) = Leaf <$> g x --- > traverse g (Node l k r) = Node <$> traverse g l <*> g k <*> traverse g r --- --- This definition works for any __@g :: a -> f b@__, with __@f@__ an --- Applicative functor, as the laws for @('<*>')@ imply the requisite --- associativity. --- --- We can add an explicit non-default 'mapM' if desired: --- --- > mapM g Empty = return Empty --- > mapM g (Leaf x) = Leaf <$> g x --- > mapM g (Node l k r) = do --- > ml <- mapM g l --- > mk <- g k --- > mr <- mapM g r --- > return $ Node ml mk mr --- --- See [Construction](#construction) below for a more detailed exploration of --- the general case, but as mentioned in [Overview](#overview) above, instance --- definitions are typically rather simple, all the interesting behaviour is a --- result of an interesting choice of 'Applicative' functor for a traversal. - --- $tree_order --- --- It is perhaps worth noting that the traversal defined above gives an --- /in-order/ sequencing of the elements. If instead you want either --- /pre-order/ (parent first, then child nodes) or post-order (child nodes --- first, then parent) sequencing, you can define the instance accordingly: --- --- > inOrderNode :: Tree a -> a -> Tree a -> Tree a --- > inOrderNode l x r = Node l x r --- > --- > preOrderNode :: a -> Tree a -> Tree a -> Tree a --- > preOrderNode x l r = Node l x r --- > --- > postOrderNode :: Tree a -> Tree a -> a -> Tree a --- > postOrderNode l r x = Node l x r --- > --- > -- Traversable instance with in-order traversal --- > instance Traversable Tree where --- > traverse g t = case t of --- > Empty -> pure Empty --- > Leaf x -> Leaf <$> g x --- > Node l x r -> inOrderNode <$> traverse g l <*> g x <*> traverse g r --- > --- > -- Traversable instance with pre-order traversal --- > instance Traversable Tree where --- > traverse g t = case t of --- > Empty -> pure Empty --- > Leaf x -> Leaf <$> g x --- > Node l x r -> preOrderNode <$> g x <*> traverse g l <*> traverse g r --- > --- > -- Traversable instance with post-order traversal --- > instance Traversable Tree where --- > traverse g t = case t of --- > Empty -> pure Empty --- > Leaf x -> Leaf <$> g x --- > Node l x r -> postOrderNode <$> traverse g l <*> traverse g r <*> g x --- --- Since the same underlying Tree structure is used in all three cases, it is --- possible to use @newtype@ wrappers to make all three available at the same --- time! The user need only wrap the root of the tree in the appropriate --- @newtype@ for the desired traversal order. Tne associated instance --- definitions are shown below (see [coercion](#coercion) if unfamiliar with --- the use of 'coerce' in the sample code): --- --- > {-# LANGUAGE ScopedTypeVariables, TypeApplications #-} --- > --- > -- Default in-order traversal --- > --- > import GHC.Internal.Data.Coerce (coerce) --- > import GHC.Internal.Data.Traversable --- > --- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) --- > instance Functor Tree where fmap = fmapDefault --- > instance Foldable Tree where foldMap = foldMapDefault --- > --- > instance Traversable Tree where --- > traverse _ Empty = pure Empty --- > traverse g (Leaf a) = Leaf <$> g a --- > traverse g (Node l a r) = Node <$> traverse g l <*> g a <*> traverse g r --- > --- > -- Optional pre-order traversal --- > --- > newtype PreOrderTree a = PreOrderTree (Tree a) --- > instance Functor PreOrderTree where fmap = fmapDefault --- > instance Foldable PreOrderTree where foldMap = foldMapDefault --- > --- > instance Traversable PreOrderTree where --- > traverse _ (PreOrderTree Empty) = pure $ preOrderEmpty --- > traverse g (PreOrderTree (Leaf x)) = preOrderLeaf <$> g x --- > traverse g (PreOrderTree (Node l x r)) = preOrderNode --- > <$> g x --- > <*> traverse g (coerce l) --- > <*> traverse g (coerce r) --- > --- > preOrderEmpty :: forall a. PreOrderTree a --- > preOrderEmpty = coerce (Empty @a) --- > preOrderLeaf :: forall a. a -> PreOrderTree a --- > preOrderLeaf = coerce (Leaf @a) --- > preOrderNode :: a -> PreOrderTree a -> PreOrderTree a -> PreOrderTree a --- > preOrderNode x l r = coerce (Node (coerce l) x (coerce r)) --- > --- > -- Optional post-order traversal --- > --- > newtype PostOrderTree a = PostOrderTree (Tree a) --- > instance Functor PostOrderTree where fmap = fmapDefault --- > instance Foldable PostOrderTree where foldMap = foldMapDefault --- > --- > instance Traversable PostOrderTree where --- > traverse _ (PostOrderTree Empty) = pure postOrderEmpty --- > traverse g (PostOrderTree (Leaf x)) = postOrderLeaf <$> g x --- > traverse g (PostOrderTree (Node l x r)) = postOrderNode --- > <$> traverse g (coerce l) --- > <*> traverse g (coerce r) --- > <*> g x --- > --- > postOrderEmpty :: forall a. PostOrderTree a --- > postOrderEmpty = coerce (Empty @a) --- > postOrderLeaf :: forall a. a -> PostOrderTree a --- > postOrderLeaf = coerce (Leaf @a) --- > postOrderNode :: PostOrderTree a -> PostOrderTree a -> a -> PostOrderTree a --- > postOrderNode l r x = coerce (Node (coerce l) x (coerce r)) --- --- With the above, given a sample tree: --- --- > inOrder :: Tree Int --- > inOrder = Node (Node (Leaf 10) 3 (Leaf 20)) 5 (Leaf 42) --- --- we have: --- --- > import GHC.Internal.Data.Foldable (toList) --- > print $ toList inOrder --- > [10,3,20,5,42] --- > --- > print $ toList (coerce inOrder :: PreOrderTree Int) --- > [5,3,10,20,42] --- > --- > print $ toList (coerce inOrder :: PostOrderTree Int) --- > [10,20,3,42,5] --- --- You would typically define instances for additional common type classes, --- such as 'Eq', 'Ord', 'Show', etc. - ------------------- - --- $construction --- --- #construction# --- In order to be able to reason about how a given type of 'Applicative' --- effects will be sequenced through a general 'Traversable' structure by its --- 'traversable' and related methods, it is helpful to look more closely --- at how a general 'traverse' method is implemented. We'll look at how --- general traversals are constructed primarily with a view to being able --- to predict their behaviour as a user, even if you're not defining your --- own 'Traversable' instances. --- --- Traversable structures __@t a@__ are assembled incrementally from their --- constituent parts, perhaps by prepending or appending individual elements of --- type __@a@__, or, more generally, by recursively combining smaller composite --- traversable building blocks that contain multiple such elements. --- --- As in the [tree example](#tree) above, the components being combined are --- typically pieced together by a suitable /constructor/, i.e. a function --- taking two or more arguments that returns a composite value. --- --- The 'traverse' method enriches simple incremental construction with --- threading of 'Applicative' effects of some function __@g :: a -> f b@__. --- --- The basic building blocks we'll use to model the construction of 'traverse' --- are a hypothetical set of elementary functions, some of which may have --- direct analogues in specific @Traversable@ structures. For example, the --- __@(':')@__ constructor is an analogue for lists of @prepend@ or the more --- general @combine@. --- --- > empty :: t a -- build an empty container --- > singleton :: a -> t a -- build a one-element container --- > prepend :: a -> t a -> t a -- extend by prepending a new initial element --- > append :: t a -> a -> t a -- extend by appending a new final element --- > combine :: a1 -> a2 -> ... -> an -> t a -- combine multiple inputs --- --- * An empty structure has no elements of type __@a@__, so there's nothing --- to which __@g@__ can be applied, but since we need an output of type --- __@f (t b)@__, we just use the 'pure' instance of __@f@__ to wrap an --- empty of type __@t b@__: --- --- > traverse _ (empty :: t a) = pure (empty :: t b) --- --- With the List monad, /empty/ is __@[]@__, while with 'Maybe' it is --- 'Nothing'. With __@Either e a@__ we have an /empty/ case for each --- value of __@e@__: --- --- > traverse _ (Left e :: Either e a) = pure $ (Left e :: Either e b) --- --- * A singleton structure has just one element of type __@a@__, and --- 'traverse' can take that __@a@__, apply __@g :: a -> f b@__ getting an --- __@f b@__, then __@fmap singleton@__ over that, getting an __@f (t b)@__ --- as required: --- --- > traverse g (singleton a) = fmap singleton $ g a --- --- Note that if __@f@__ is __@List@__ and __@g@__ returns multiple values --- the result will be a list of multiple __@t b@__ singletons! --- --- Since 'Maybe' and 'Either' are either empty or singletons, we have --- --- > traverse _ Nothing = pure Nothing --- > traverse g (Just a) = Just <$> g a --- --- > traverse _ (Left e) = pure (Left e) --- > traverse g (Right a) = Right <$> g a --- --- For @List@, empty is __@[]@__ and @singleton@ is __@(:[])@__, so we have: --- --- > traverse _ [] = pure [] --- > traverse g [a] = fmap (:[]) (g a) --- > = (:) <$> (g a) <*> traverse g [] --- > = liftA2 (:) (g a) (traverse g []) --- --- * When the structure is built by adding one more element via __@prepend@__ --- or __@append@__, traversal amounts to: --- --- > traverse g (prepend a t0) = prepend <$> (g a) <*> traverse g t0 --- > = liftA2 prepend (g a) (traverse g t0) --- --- > traverse g (append t0 a) = append <$> traverse g t0 <*> g a --- > = liftA2 append (traverse g t0) (g a) --- --- The origin of the combinatorial product when __@f@__ is @List@ should now --- be apparent, when __@traverse g t0@__ has __@n@__ elements and __@g a@__ --- has __@m@__ elements, the /non-deterministic/ 'Applicative' instance of --- @List@ will produce a result with __@m * n@__ elements. --- --- * When combining larger building blocks, we again use __@('<*>')@__ to --- combine the traversals of the components. With bare elements __@a@__ --- mapped to __@f b@__ via __@g@__, and composite traversable --- sub-structures transformed via __@traverse g@__: --- --- > traverse g (combine a1 a2 ... an) = --- > combine <$> t1 <*> t2 <*> ... <*> tn --- > where --- > t1 = g a1 -- if a1 fills a slot of type @a@ --- > = traverse g a1 -- if a1 is a traversable substructure --- > ... ditto for the remaining constructor arguments ... --- --- The above definitions sequence the 'Applicative' effects of __@f@__ in the --- expected order while producing results of the expected shape __@t@__. --- --- For lists this becomes: --- --- > traverse g [] = pure [] --- > traverse g (x:xs) = liftA2 (:) (g a) (traverse g xs) --- --- The actual definition of 'traverse' for lists is an equivalent --- right fold in order to facilitate list /fusion/. --- --- > traverse g = foldr (\x r -> liftA2 (:) (g x) r) (pure []) - ------------------- - --- $advanced --- --- #advanced# --- In the sections below we'll examine some advanced choices of 'Applicative' --- effects that give rise to very different transformations of @Traversable@ --- structures. --- --- These examples cover the implementations of 'fmapDefault', 'foldMapDefault', --- 'mapAccumL' and 'mapAccumR' functions illustrating the use of 'Identity', --- 'Const' and stateful 'Applicative' effects. The [ZipList](#ziplist) example --- illustrates the use of a less-well known 'Applicative' instance for lists. --- --- This is optional material, which is not essential to a basic understanding of --- @Traversable@ structures. If this is your first encounter with @Traversable@ --- structures, you can come back to these at a later date. - --- $coercion --- --- #coercion# --- Some of the examples make use of an advanced Haskell feature, namely --- @newtype@ /coercion/. This is done for two reasons: --- --- * Use of 'coerce' makes it possible to avoid cluttering the code with --- functions that wrap and unwrap /newtype/ terms, which at runtime are --- indistinguishable from the underlying value. Coercion is particularly --- convenient when one would have to otherwise apply multiple newtype --- constructors to function arguments, and then peel off multiple layers --- of same from the function output. --- --- * Use of 'coerce' can produce more efficient code, by reusing the original --- value, rather than allocating space for a wrapped clone. --- --- If you're not familiar with 'coerce', don't worry, it is just a shorthand --- that, e.g., given: --- --- > newtype Foo a = MkFoo { getFoo :: a } --- > newtype Bar a = MkBar { getBar :: a } --- > newtype Baz a = MkBaz { getBaz :: a } --- > f :: Baz Int -> Bar (Foo String) --- --- makes it possible to write: --- --- > x :: Int -> String --- > x = coerce f --- --- instead of --- --- > x = getFoo . getBar . f . MkBaz - ------------------- - --- $identity --- --- #identity# --- The simplest Applicative functor is 'Identity', which just wraps and unwraps --- pure values and function application. This allows us to define --- 'fmapDefault': --- --- > {-# LANGUAGE ScopedTypeVariables, TypeApplications #-} --- > import Data.Coercible (coerce) --- > --- > fmapDefault :: forall t a b. Traversable t => (a -> b) -> t a -> t b --- > fmapDefault = coerce (traverse @t @Identity @a @b) --- --- The use of [coercion](#coercion) avoids the need to explicitly wrap and --- unwrap terms via 'Identity' and 'runIdentity'. --- --- As noted in [Overview](#overview), 'fmapDefault' can only be used to define --- the requisite 'Functor' instance of a 'Traversable' structure when the --- 'traverse' method is explicitly implemented. An infinite loop would result --- if in addition 'traverse' were defined in terms of 'sequenceA' and 'fmap'. - ------------------- - --- $stateful --- --- #stateful# --- Applicative functors that thread a changing state through a computation are --- an interesting use-case for 'traverse'. The 'mapAccumL' and 'mapAccumR' --- functions in this module are each defined in terms of such traversals. --- --- We first define a simplified (not a monad transformer) version of --- 'Control.Monad.Trans.State.State' that threads a state __@s@__ through a --- chain of computations left to right. Its @('<*>')@ operator passes the --- input state first to its left argument, and then the resulting state is --- passed to its right argument, which returns the final state. --- --- > newtype StateL s a = StateL { runStateL :: s -> (s, a) } --- > --- > instance Functor (StateL s) where --- > fmap f (StateL kx) = StateL $ \ s -> --- > let (s', x) = kx s in (s', f x) --- > --- > instance Applicative (StateL s) where --- > pure a = StateL $ \s -> (s, a) --- > (StateL kf) <*> (StateL kx) = StateL $ \ s -> --- > let { (s', f) = kf s --- > ; (s'', x) = kx s' } in (s'', f x) --- > liftA2 f (StateL kx) (StateL ky) = StateL $ \ s -> --- > let { (s', x) = kx s --- > ; (s'', y) = ky s' } in (s'', f x y) --- --- With @StateL@, we can define 'mapAccumL' as follows: --- --- > {-# LANGUAGE ScopedTypeVariables, TypeApplications #-} --- > mapAccumL :: forall t s a b. Traversable t --- > => (s -> a -> (s, b)) -> s -> t a -> (s, t b) --- > mapAccumL g s ts = coerce (traverse @t @(StateL s) @a @b) (flip g) ts s --- --- The use of [coercion](#coercion) avoids the need to explicitly wrap and --- unwrap __@newtype@__ terms. --- --- The type of __@flip g@__ is coercible to __@a -> StateL b@__, which makes it --- suitable for use with 'traverse'. As part of the Applicative --- [construction](#construction) of __@StateL (t b)@__ the state updates will --- thread left-to-right along the sequence of elements of __@t a@__. --- --- While 'mapAccumR' has a type signature identical to 'mapAccumL', it differs --- in the expected order of evaluation of effects, which must take place --- right-to-left. --- --- For this we need a variant control structure @StateR@, which threads the --- state right-to-left, by passing the input state to its right argument and --- then using the resulting state as an input to its left argument: --- --- > newtype StateR s a = StateR { runStateR :: s -> (s, a) } --- > --- > instance Functor (StateR s) where --- > fmap f (StateR kx) = StateR $ \s -> --- > let (s', x) = kx s in (s', f x) --- > --- > instance Applicative (StateR s) where --- > pure a = StateR $ \s -> (s, a) --- > (StateR kf) <*> (StateR kx) = StateR $ \ s -> --- > let { (s', x) = kx s --- > ; (s'', f) = kf s' } in (s'', f x) --- > liftA2 f (StateR kx) (StateR ky) = StateR $ \ s -> --- > let { (s', y) = ky s --- > ; (s'', x) = kx s' } in (s'', f x y) --- --- With @StateR@, we can define 'mapAccumR' as follows: --- --- > {-# LANGUAGE ScopedTypeVariables, TypeApplications #-} --- > mapAccumR :: forall t s a b. Traversable t --- > => (s -> a -> (s, b)) -> s -> t a -> (s, t b) --- > mapAccumR g s0 ts = coerce (traverse @t @(StateR s) @a @b) (flip g) ts s0 --- --- The use of [coercion](#coercion) avoids the need to explicitly wrap and --- unwrap __@newtype@__ terms. --- --- Various stateful traversals can be constructed from 'mapAccumL' and --- 'mapAccumR' for suitable choices of @g@, or built directly along similar --- lines. - ------------------- - --- $phantom --- --- #phantom# --- The 'Const' Functor enables applications of 'traverse' that summarise the --- input structure to an output value without constructing any output values --- of the same type or shape. --- --- As noted [above](#overview), the @Foldable@ superclass constraint is --- justified by the fact that it is possible to construct 'foldMap', 'foldr', --- etc., from 'traverse'. The technique used is useful in its own right, and --- is explored below. --- --- A key feature of folds is that they can reduce the input structure to a --- summary value. Often neither the input structure nor a mutated clone is --- needed once the fold is computed, and through list fusion the input may not --- even have been memory resident in its entirety at the same time. --- --- The 'traverse' method does not at first seem to be a suitable building block --- for folds, because its return value __@f (t b)@__ appears to retain mutated --- copies of the input structure. But the presence of __@t b@__ in the type --- signature need not mean that terms of type __@t b@__ are actually embedded --- in __@f (t b)@__. The simplest way to elide the excess terms is by basing --- the Applicative functor used with 'traverse' on 'Const'. --- --- Not only does __@Const a b@__ hold just an __@a@__ value, with the __@b@__ --- parameter merely a /phantom/ type, but when __@m@__ has a 'Monoid' instance, --- __@Const m@__ is an 'Applicative' functor: --- --- > import GHC.Internal.Data.Coerce (coerce) --- > newtype Const a b = Const { getConst :: a } deriving (Eq, Ord, Show) -- etc. --- > instance Functor (Const m) where fmap = const coerce --- > instance Monoid m => Applicative (Const m) where --- > pure _ = Const mempty --- > (<*>) = coerce (mappend :: m -> m -> m) --- > liftA2 _ = coerce (mappend :: m -> m -> m) --- --- The use of [coercion](#coercion) avoids the need to explicitly wrap and --- unwrap __@newtype@__ terms. --- --- We can therefore define a specialisation of 'traverse': --- --- > {-# LANGUAGE ScopedTypeVariables, TypeApplications #-} --- > traverseC :: forall t a m. (Monoid m, Traversable t) --- > => (a -> Const m ()) -> t a -> Const m (t ()) --- > traverseC = traverse @t @(Const m) @a @() --- --- For which the Applicative [construction](#construction) of 'traverse' --- leads to: --- --- prop> null ts ==> traverseC g ts = Const mempty --- prop> traverseC g (prepend x xs) = Const (g x) <> traverseC g xs --- --- In other words, this makes it possible to define: --- --- > {-# LANGUAGE ScopedTypeVariables, TypeApplications #-} --- > foldMapDefault :: forall t a m. (Monoid m, Traversable t) => (a -> m) -> t a -> m --- > foldMapDefault = coerce (traverse @t @(Const m) @a @()) --- --- Which is sufficient to define a 'Foldable' superclass instance: --- --- The use of [coercion](#coercion) avoids the need to explicitly wrap and --- unwrap __@newtype@__ terms. --- --- > instance Traversable t => Foldable t where foldMap = foldMapDefault --- --- It may however be instructive to also directly define candidate default --- implementations of 'foldr' and 'foldl'', which take a bit more machinery --- to construct: --- --- > {-# LANGUAGE ScopedTypeVariables, TypeApplications #-} --- > import GHC.Internal.Data.Coerce (coerce) --- > import GHC.Internal.Data.Functor.Const (Const(..)) --- > import Data.Semigroup (Dual(..), Endo(..)) --- > import GHC.Internal.Exts (oneShot) --- > --- > foldrDefault :: forall t a b. Traversable t --- > => (a -> b -> b) -> b -> t a -> b --- > foldrDefault f z = \t -> --- > coerce (traverse @t @(Const (Endo b)) @a @()) f t z --- > --- > foldlDefault' :: forall t a b. Traversable t => (b -> a -> b) -> b -> t a -> b --- > foldlDefault' f z = \t -> --- > coerce (traverse @t @(Const (Dual (Endo b))) @a @()) f' t z --- > where --- > f' :: a -> b -> b --- > f' a = oneShot $ \ b -> b `seq` f b a --- --- In the above we're using the __@'Data.Monoid.Endo' b@__ 'Monoid' and its --- 'Dual' to compose a sequence of __@b -> b@__ accumulator updates in either --- left-to-right or right-to-left order. --- --- The use of 'seq' in the definition of __@foldlDefault'@__ ensures strictness --- in the accumulator. --- --- The use of [coercion](#coercion) avoids the need to explicitly wrap and --- unwrap __@newtype@__ terms. --- --- The 'GHC.Internal.Exts.oneShot' function gives a hint to the compiler that aids in --- correct optimisation of lambda terms that fire at most once (for each --- element __@a@__) and so should not try to pre-compute and re-use --- subexpressions that pay off only on repeated execution. Otherwise, it is --- just the identity function. - ------------------- - --- $ziplist --- --- #ziplist# --- As a warm-up for looking at the 'ZipList' 'Applicative' functor, we'll first --- look at a simpler analogue. First define a fixed width 2-element @Vec2@ --- type, whose 'Applicative' instance combines a pair of functions with a pair of --- values by applying each function to the corresponding value slot: --- --- > data Vec2 a = Vec2 a a --- > instance Functor Vec2 where --- > fmap f (Vec2 a b) = Vec2 (f a) (f b) --- > instance Applicative Vec2 where --- > pure x = Vec2 x x --- > liftA2 f (Vec2 a b) (Vec2 p q) = Vec2 (f a p) (f b q) --- > instance Foldable Vec2 where --- > foldr f z (Vec2 a b) = f a (f b z) --- > foldMap f (Vec2 a b) = f a <> f b --- > instance Traversable Vec2 where --- > traverse f (Vec2 a b) = Vec2 <$> f a <*> f b --- --- Along with a similar definition for fixed width 3-element vectors: --- --- > data Vec3 a = Vec3 a a a --- > instance Functor Vec3 where --- > fmap f (Vec3 x y z) = Vec3 (f x) (f y) (f z) --- > instance Applicative Vec3 where --- > pure x = Vec3 x x x --- > liftA2 f (Vec3 p q r) (Vec3 x y z) = Vec3 (f p x) (f q y) (f r z) --- > instance Foldable Vec3 where --- > foldr f z (Vec3 a b c) = f a (f b (f c z)) --- > foldMap f (Vec3 a b c) = f a <> f b <> f c --- > instance Traversable Vec3 where --- > traverse f (Vec3 a b c) = Vec3 <$> f a <*> f b <*> f c --- --- With the above definitions, @'sequenceA'@ (same as @'traverse' 'id'@) acts --- as a /matrix transpose/ operation on @Vec2 (Vec3 Int)@ producing a --- corresponding @Vec3 (Vec2 Int)@: --- --- Let __@t = Vec2 (Vec3 1 2 3) (Vec3 4 5 6)@__ be our 'Traversable' structure, --- and __@g = id :: Vec3 Int -> Vec3 Int@__ be the function used to traverse --- __@t@__. We then have: --- --- > traverse g t = Vec2 <$> (Vec3 1 2 3) <*> (Vec3 4 5 6) --- > = Vec3 (Vec2 1 4) (Vec2 2 5) (Vec2 3 6) --- --- This construction can be generalised from fixed width vectors to variable --- length lists via 'Control.Applicative.ZipList'. This gives a transpose --- operation that works well for lists of equal length. If some of the lists --- are longer than others, they're truncated to the longest common length. --- --- We've already looked at the standard 'Applicative' instance of @List@ for --- which applying __@m@__ functions __@f1, f2, ..., fm@__ to __@n@__ input --- values __@a1, a2, ..., an@__ produces __@m * n@__ outputs: --- --- >>> :set -XTupleSections --- >>> [("f1",), ("f2",), ("f3",)] <*> [1,2] --- [("f1",1),("f1",2),("f2",1),("f2",2),("f3",1),("f3",2)] --- --- There are however two more common ways to turn lists into 'Applicative' --- control structures. The first is via __@'Const' [a]@__, since lists are --- monoids under concatenation, and we've already seen that __@'Const' m@__ is --- an 'Applicative' functor when __@m@__ is a 'Monoid'. The second, is based --- on 'GHC.Internal.Data.List.zipWith', and is called 'Control.Applicative.ZipList': --- --- > {-# LANGUAGE GeneralizedNewtypeDeriving #-} --- > newtype ZipList a = ZipList { getZipList :: [a] } --- > deriving (Show, Eq, ..., Functor) --- > --- > instance Applicative ZipList where --- > liftA2 f (ZipList xs) (ZipList ys) = ZipList $ zipWith f xs ys --- > pure x = repeat x --- --- The 'liftA2' definition is clear enough, instead of applying __@f@__ to each --- pair __@(x, y)@__ drawn independently from the __@xs@__ and __@ys@__, only --- corresponding pairs at each index in the two lists are used. --- --- The definition of 'pure' may look surprising, but it is needed to ensure --- that the instance is lawful: --- --- prop> liftA2 f (pure x) ys == fmap (f x) ys --- --- Since __@ys@__ can have any length, we need to provide an infinite supply --- of __@x@__ values in __@pure x@__ in order to have a value to pair with --- each element __@y@__. --- --- When 'Control.Applicative.ZipList' is the 'Applicative' functor used in the --- [construction](#construction) of a traversal, a ZipList holding a partially --- built structure with __@m@__ elements is combined with a component holding --- __@n@__ elements via 'zipWith', resulting in __@min m n@__ outputs! --- --- Therefore 'traverse' with __@g :: a -> ZipList b@__ will produce a @ZipList@ --- of __@t b@__ structures whose element count is the minimum length of the --- ZipLists __@g a@__ with __@a@__ ranging over the elements of __@t@__. When --- __@t@__ is empty, the length is infinite (as expected for a minimum of an --- empty set). --- --- If the structure __@t@__ holds values of type __@ZipList a@__, we can use --- the identity function __@id :: ZipList a -> ZipList a@__ for the first --- argument of 'traverse': --- --- > traverse (id :: ZipList a -> ZipList a) :: t (ZipList a) -> ZipList (t a) --- --- The number of elements in the output @ZipList@ will be the length of the --- shortest @ZipList@ element of __@t@__. Each output __@t a@__ will have the --- /same shape/ as the input __@t (ZipList a)@__, i.e. will share its number of --- elements. --- --- If we think of the elements of __@t (ZipList a)@__ as its rows, and the --- elements of each individual @ZipList@ as the columns of that row, we see --- that our traversal implements a /transpose/ operation swapping the rows --- and columns of __@t@__, after first truncating all the rows to the column --- count of the shortest one. --- --- Since in fact __@'traverse' id@__ is just 'sequenceA' the above boils down --- to a rather concise definition of /transpose/, with [coercion](#coercion) --- used to implicitly wrap and unwrap the @ZipList@ @newtype@ as needed, giving --- a function that operates on a list of lists: --- --- >>> {-# LANGUAGE ScopedTypeVariables #-} --- >>> import Control.Applicative (ZipList(..)) --- >>> import GHC.Internal.Data.Coerce (coerce) --- >>> --- >>> transpose :: forall a. [[a]] -> [[a]] --- >>> transpose = coerce (sequenceA :: [ZipList a] -> ZipList [a]) --- >>> --- >>> transpose [[1,2,3],[4..],[7..]] --- [[1,4,7],[2,5,8],[3,6,9]] --- --- The use of [coercion](#coercion) avoids the need to explicitly wrap and --- unwrap __@ZipList@__ terms. - ------------------- - --- $laws --- --- #laws# --- A definition of 'traverse' must satisfy the following laws: --- --- [Naturality] --- @t . 'traverse' f = 'traverse' (t . f)@ --- for every applicative transformation @t@ --- --- [Identity] --- @'traverse' 'Identity' = 'Identity'@ --- --- [Composition] --- @'traverse' ('Data.Functor.Compose.Compose' . 'fmap' g . f) --- = 'Data.Functor.Compose.Compose' . 'fmap' ('traverse' g) . 'traverse' f@ --- --- A definition of 'sequenceA' must satisfy the following laws: --- --- [Naturality] --- @t . 'sequenceA' = 'sequenceA' . 'fmap' t@ --- for every applicative transformation @t@ --- --- [Identity] --- @'sequenceA' . 'fmap' 'Identity' = 'Identity'@ --- --- [Composition] --- @'sequenceA' . 'fmap' 'Data.Functor.Compose.Compose' --- = 'Data.Functor.Compose.Compose' . 'fmap' 'sequenceA' . 'sequenceA'@ --- --- where an /applicative transformation/ is a function --- --- @t :: (Applicative f, Applicative g) => f a -> g a@ --- --- preserving the 'Applicative' operations, i.e. --- --- @ --- t ('pure' x) = 'pure' x --- t (f '<*>' x) = t f '<*>' t x --- @ --- --- and the identity functor 'Identity' and composition functors --- 'Data.Functor.Compose.Compose' are from "Data.Functor.Identity" and --- "Data.Functor.Compose". --- --- A result of the naturality law is a purity law for 'traverse' --- --- @'traverse' 'pure' = 'pure'@ --- --- The superclass instances should satisfy the following: --- --- * In the 'Functor' instance, 'fmap' should be equivalent to traversal --- with the identity applicative functor ('fmapDefault'). --- --- * In the 'Foldable' instance, 'GHC.Internal.Data.Foldable.foldMap' should be --- equivalent to traversal with a constant applicative functor --- ('foldMapDefault'). --- --- Note: the 'Functor' superclass means that (in GHC) Traversable structures --- cannot impose any constraints on the element type. A Haskell implementation --- that supports constrained functors could make it possible to define --- constrained @Traversable@ structures. - ------------------- - --- $also --- --- * \"The Essence of the Iterator Pattern\", --- by Jeremy Gibbons and Bruno Oliveira, --- in /Mathematically-Structured Functional Programming/, 2006, online at --- <http://www.cs.ox.ac.uk/people/jeremy.gibbons/publications/#iterator>. --- --- * \"Applicative Programming with Effects\", --- by Conor McBride and Ross Paterson, --- /Journal of Functional Programming/ 18:1 (2008) 1-13, online at --- <http://www.soi.city.ac.uk/~ross/papers/Applicative.html>. --- --- * \"An Investigation of the Laws of Traversals\", --- by Mauro Jaskelioff and Ondrej Rypacek, --- in /Mathematically-Structured Functional Programming/, 2012, online at --- <http://arxiv.org/pdf/1202.2919>. diff --git a/libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs b/libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs index 40d4f4148bce..b9fd71eaa258 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs @@ -472,7 +472,7 @@ mkTrApp a b -- See Note [Kind caching], Wrinkle 2 -- | Construct a representation for a type application that -- may be a saturated arrow type. This is renamed to mkTrApp in --- GHC.Internal.Type.Reflection.Unsafe +-- Type.Reflection.Unsafe mkTrAppChecked :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep (a :: k1 -> k2) -> TypeRep (b :: k1) diff --git a/libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs b/libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs index bbc1e6a4752e..47fe8f2edfc9 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs @@ -22,7 +22,6 @@ module GHC.Internal.Debug.Trace ( -- * Tracing - -- $tracing trace, traceId, traceShow, @@ -36,14 +35,12 @@ module GHC.Internal.Debug.Trace ( putTraceMsg, -- * Eventlog tracing - -- $eventlog_tracing traceEvent, traceEventWith, traceEventIO, flushEventLog, -- * Execution phase markers - -- $markers traceMarker, traceMarkerIO, ) where @@ -58,24 +55,6 @@ import GHC.Internal.Show import GHC.Internal.Stack import GHC.Internal.Data.List (null, partition) --- $setup --- >>> import Prelude - --- $tracing --- --- The 'trace', 'traceShow' and 'traceIO' functions print messages to an output --- stream. They are intended for \"printf debugging\", that is: tracing the flow --- of execution and printing interesting values. --- --- All these functions evaluate the message completely before printing --- it; so if the message is not fully defined, none of it will be --- printed. --- --- The usual output stream is 'GHC.Internal.System.IO.stderr'. For Windows GUI applications --- (that have no stderr) the output is directed to the Windows debug console. --- Some implementations of these functions may decorate the string that\'s --- output to indicate that you\'re tracing. - -- | The 'traceIO' function outputs the trace message from the IO monad. -- This sequences the output with respect to other IO actions. -- @@ -258,19 +237,6 @@ traceStack str expr = unsafePerformIO $ do when (not (null stack)) $ traceIO (renderStack stack) return expr - --- $eventlog_tracing --- --- Eventlog tracing is a performance profiling system. These functions emit --- extra events into the eventlog. In combination with eventlog profiling --- tools these functions can be used for monitoring execution and --- investigating performance problems. --- --- Currently only GHC provides eventlog profiling, see the GHC user guide for --- details on how to use it. These function exists for other Haskell --- implementations but no events are emitted. Note that the string message is --- always evaluated, whether or not profiling is available or enabled. - {-# NOINLINE traceEvent #-} -- | The 'traceEvent' function behaves like 'trace' with the difference that -- the message is emitted to the eventlog, if eventlog profiling is available @@ -308,25 +274,6 @@ traceEventIO msg = traceEventWith :: (a -> String) -> a -> a traceEventWith f a = traceEvent (f a) a --- $markers --- --- When looking at a profile for the execution of a program we often want to --- be able to mark certain points or phases in the execution and see that --- visually in the profile. --- --- For example, a program might have several distinct phases with different --- performance or resource behaviour in each phase. To properly interpret the --- profile graph we really want to see when each phase starts and ends. --- --- Markers let us do this: we can annotate the program to emit a marker at --- an appropriate point during execution and then see that in a profile. --- --- Currently this feature is only supported in GHC by the eventlog tracing --- system, but in future it may also be supported by the heap profiling or --- other profiling tools. These function exists for other Haskell --- implementations but they have no effect. Note that the string message is --- always evaluated, whether or not profiling is available or enabled. - {-# NOINLINE traceMarker #-} -- | The 'traceMarker' function emits a marker to the eventlog, if eventlog -- profiling is available and enabled at runtime. The @String@ is the name of diff --git a/libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs-boot b/libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs-boot index 58f30fb4a1a5..aed660f3b046 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs-boot +++ b/libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs-boot @@ -26,8 +26,6 @@ ----------------------------------------------------------------------------- module GHC.Internal.Debug.Trace ( - -- * Tracing - -- $tracing trace, traceId, traceShow, @@ -36,14 +34,8 @@ module GHC.Internal.Debug.Trace ( traceIO, traceM, traceShowM, - - -- * Eventlog tracing - -- $eventlog_tracing traceEvent, traceEventIO, - - -- * Execution phase markers - -- $markers traceMarker, traceMarkerIO, ) where diff --git a/libraries/ghc-internal/src/GHC/Internal/Foreign/StablePtr.hs b/libraries/ghc-internal/src/GHC/Internal/Foreign/StablePtr.hs index ae16e6b283ca..ef78ee27a8af 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Foreign/StablePtr.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Foreign/StablePtr.hs @@ -25,23 +25,7 @@ module GHC.Internal.Foreign.StablePtr , freeStablePtr , castStablePtrToPtr , castPtrToStablePtr - , -- ** The C-side interface - - -- $cinterface ) where import GHC.Internal.Stable --- $cinterface --- --- The following definition is available to C programs inter-operating with --- Haskell code when including the header @HsFFI.h@. --- --- > typedef void *HsStablePtr; /* C representation of a StablePtr */ --- --- Note that no assumptions may be made about the values representing stable --- pointers. In fact, they need not even be valid memory addresses. The only --- guarantee provided is that if they are passed back to Haskell land, the --- function 'deRefStablePtr' will be able to reconstruct the --- Haskell value referred to by the stable pointer. - diff --git a/libraries/ghc-internal/src/GHC/Internal/ForeignPtr.hs b/libraries/ghc-internal/src/GHC/Internal/ForeignPtr.hs index 315134367289..50e93eabfb69 100644 --- a/libraries/ghc-internal/src/GHC/Internal/ForeignPtr.hs +++ b/libraries/ghc-internal/src/GHC/Internal/ForeignPtr.hs @@ -51,8 +51,6 @@ module GHC.Internal.ForeignPtr touchForeignPtr, -- * Finalization finalizeForeignPtr - -- * Commentary - -- $commentary ) where import GHC.Internal.Foreign.Storable @@ -635,45 +633,3 @@ finalizeForeignPtr (ForeignPtr _ c) = case c of PlainPtr{} -> return () FinalPtr{} -> return () -{- $commentary - -This is a high-level overview of how 'ForeignPtr' works. -The implementation of 'ForeignPtr' must accomplish several goals: - -1. Invoke a finalizer once a foreign pointer becomes unreachable. -2. Support augmentation of finalizers, i.e. 'addForeignPtrFinalizer'. - As a motivating example, suppose that the payload of a foreign - pointer is C struct @bar@ that has an optionally NULL pointer field - @foo@ to an unmanaged heap object. Initially, @foo@ is NULL, and - later the program uses @malloc@, initializes the object, and assigns - @foo@ the address returned by @malloc@. When the foreign pointer - becomes unreachable, it is now necessary to first @free@ the object - pointed to by @foo@ and then invoke whatever finalizer was associated - with @bar@. That is, finalizers must be invoked in the opposite order - they are added. -3. Allow users to invoke a finalizer promptly if they know that the - foreign pointer is unreachable, i.e. 'finalizeForeignPtr'. - -How can these goals be accomplished? Goal 1 suggests that weak references -and finalizers (via 'Weak#' and 'mkWeak#') are necessary. But how should -they be used and what should their key be? Certainly not 'ForeignPtr' or -'ForeignPtrContents'. See the warning in "GHC.Weak" about weak pointers with -lifted (non-primitive) keys. The two finalizer-supporting data constructors of -'ForeignPtr' have an @'IORef' 'Finalizers'@ (backed by 'MutVar#') field. -This gets used in two different ways depending on the kind of finalizer: - -* 'HaskellFinalizers': The first @addForeignPtrConcFinalizer_@ call uses - 'mkWeak#' to attach the finalizer @foreignPtrFinalizer@ to the 'MutVar#'. - The resulting 'Weak#' is discarded (see @addForeignPtrConcFinalizer_@). - Subsequent calls to @addForeignPtrConcFinalizer_@ (goal 2) just add - finalizers onto the list in the 'HaskellFinalizers' data constructor. -* 'CFinalizers': The first 'addForeignPtrFinalizer' call uses - 'mkWeakNoFinalizer#' to create a 'Weak#'. The 'Weak#' is preserved in the - 'CFinalizers' data constructor. Both the first call and subsequent - calls (goal 2) use 'addCFinalizerToWeak#' to attach finalizers to the - 'Weak#' itself. Also, see Note [MallocPtr finalizers] for discussion of - the key and value of this 'Weak#'. - -In either case, the runtime invokes the appropriate finalizers when the -'ForeignPtr' becomes unreachable. --} diff --git a/libraries/ghc-internal/src/GHC/Internal/System/IO.hs b/libraries/ghc-internal/src/GHC/Internal/System/IO.hs index 5bc4468a5f59..5e733f7e09e3 100644 --- a/libraries/ghc-internal/src/GHC/Internal/System/IO.hs +++ b/libraries/ghc-internal/src/GHC/Internal/System/IO.hs @@ -64,10 +64,6 @@ module GHC.Internal.System.IO ( writeFile, appendFile, - -- ** File locking - - -- $locking - -- * Operations on handles -- ** Determining and changing the size of a file @@ -670,21 +666,3 @@ output_flags = std_flags .|. o_CREAT std_flags, output_flags, rw_flags :: CInt std_flags = o_NONBLOCK .|. o_NOCTTY rw_flags = output_flags .|. o_RDWR - --- $locking --- Implementations should enforce as far as possible, at least locally to the --- Haskell process, multiple-reader single-writer locking on files. --- That is, /there may either be many handles on the same file which manage input, or just one handle on the file which manages output/. If any --- open or semi-closed handle is managing a file for output, no new --- handle can be allocated for that file. If any open or semi-closed --- handle is managing a file for input, new handles can only be allocated --- if they do not manage output. Whether two files are the same is --- implementation-dependent, but they should normally be the same if they --- have the same absolute path name and neither has been renamed, for --- example. --- --- /Warning/: the 'readFile' operation holds a semi-closed handle on --- the file until the entire contents of the file have been consumed. --- It follows that an attempt to write to a file (using 'writeFile', for --- example) that was earlier opened by 'readFile' will usually result in --- failure with 'GHC.Internal.System.IO.Error.isAlreadyInUseError'. -- GitLab