for package:rebase

for is traverse with its arguments flipped. For a version that ignores the results see for_.
forAccumM is mapAccumM with the arguments rearranged.
forM is mapM with its arguments flipped. For a version that ignores the results see forM_.
forM_ is mapM_ with its arguments flipped. For a version that doesn't ignore the results see forM. forM_ is just like for_, but specialised to monadic actions.
for_ is traverse_ with its arguments flipped. For a version that doesn't ignore the results see for. This is forM_ generalised to Applicative actions. for_ is just like forM_, but generalised to Applicative actions.

Examples

Basic usage:
>>> for_ [1..4] print
1
2
3
4
a variant of deepseq that is useful in some circumstances:
force x = x `deepseq` x
force x fully evaluates x, and then returns it. Note that force x only performs evaluation when the value of force x itself is demanded, so essentially it turns shallow evaluation into deep evaluation. force can be conveniently used in combination with ViewPatterns:
{-# LANGUAGE BangPatterns, ViewPatterns #-}
import Control.DeepSeq

someFun :: ComplexData -> SomeResult
someFun (force -> !arg) = {- 'arg' will be fully evaluated -}
Another useful application is to combine force with evaluate in order to force deep evaluation relative to other IO operations:
import Control.Exception (evaluate)
import Control.DeepSeq

main = do
result <- evaluate $ force $ pureComputation
{- 'result' will be fully evaluated at this point -}
return ()
Finally, here's an exception safe variant of the readFile' example:
readFile' :: FilePath -> IO String
readFile' fn = bracket (openFile fn ReadMode) hClose $ \h ->
evaluate . force =<< hGetContents h
Repeat an action indefinitely.

Examples

A common use of forever is to process input from network sockets, Handles, and channels (e.g. MVar and Chan). For example, here is how we might implement an echo server, using forever both to listen for client connections on a network socket and to echo client input on client connection handles:
echoServer :: Socket -> IO ()
echoServer socket = forever $ do
client <- accept socket
forkFinally (echo client) (\_ -> hClose client)
where
echo :: Handle -> IO ()
echo client = forever $
hGetLine client >>= hPutStrLn client
Note that "forever" isn't necessarily non-terminating. If the action is in a MonadPlus and short-circuits after some number of iterations. then forever actually returns mzero, effectively short-circuiting its caller.
Fork a thread and call the supplied function when the thread is about to terminate, with an exception or a returned value. The function is called with asynchronous exceptions masked.
forkFinally action and_then =
mask $ \restore ->
forkIO $ try (restore action) >>= and_then
This function is useful for informing the parent when a child terminates, for example.
Creates a new thread to run the IO computation passed as the first argument, and returns the ThreadId of the newly created thread. The new thread will be a lightweight, unbound thread. Foreign calls made by this thread are not guaranteed to be made by any particular OS thread; if you need foreign calls to be made by a particular OS thread, then use forkOS instead. The new thread inherits the masked state of the parent (see mask). The newly created thread has an exception handler that discards the exceptions BlockedIndefinitelyOnMVar, BlockedIndefinitelyOnSTM, and ThreadKilled, and passes all other exceptions to the uncaught exception handler. WARNING: Exceptions in the new thread will not be rethrown in the thread that created it. This means that you might be completely unaware of the problem if/when this happens. You may want to use the async library instead.
Like forkIO, but the child thread is passed a function that can be used to unmask asynchronous exceptions. This function is typically used in the following way
... mask_ $ forkIOWithUnmask $ \unmask ->
catch (unmask ...) handler
so that the exception handler in the child thread is established with asynchronous exceptions masked, meanwhile the main body of the child thread is executed in the unmasked state. Note that the unmask function passed to the child thread should only be used in that thread; the behaviour is undefined if it is invoked in a different thread.
Like forkIO, this sparks off a new thread to run the IO computation passed as the first argument, and returns the ThreadId of the newly created thread. However, forkOS creates a bound thread, which is necessary if you need to call foreign (non-Haskell) libraries that make use of thread-local state, such as OpenGL (see Control.Concurrent#boundthreads). Using forkOS instead of forkIO makes no difference at all to the scheduling behaviour of the Haskell runtime system. It is a common misconception that you need to use forkOS instead of forkIO to avoid blocking all the Haskell threads when making a foreign call; this isn't the case. To allow foreign calls to be made without blocking all the Haskell threads (with GHC), it is only necessary to use the -threaded option when linking your program, and to make sure the foreign import is not marked unsafe.
Like forkIOWithUnmask, but the child thread is a bound thread, as with forkOS.
Like forkIO, but lets you specify on which capability the thread should run. Unlike a forkIO thread, a thread created by forkOn will stay on the same capability for its entire lifetime (forkIO threads can migrate between capabilities according to the scheduling policy). forkOn is useful for overriding the scheduling policy when you know in advance how best to distribute the threads. The Int argument specifies a capability number (see getNumCapabilities). Typically capabilities correspond to physical processors, but the exact behaviour is implementation-dependent. The value passed to forkOn is interpreted modulo the total number of capabilities as returned by getNumCapabilities. GHC note: the number of capabilities is specified by the +RTS -N option when the program is started. Capabilities can be fixed to actual processor cores with +RTS -qa if the underlying operating system supports that, although in practice this is usually unnecessary (and may actually degrade performance in some cases - experimentation is recommended).
Like forkIOWithUnmask, but the child thread is pinned to the given CPU, as with forkOn.
Substitute various time-related information for each %-code in the string, as per formatCharacter. The general form is %<modifier><width><alternate><specifier>, where <modifier>, <width>, and <alternate> are optional.

<modifier>

glibc-style modifiers can be used before the specifier (here marked as z):
  • %-z no padding
  • %_z pad with spaces
  • %0z pad with zeros
  • %^z convert to upper case
  • %#z convert to lower case (consistently, unlike glibc)

<width>

Width digits can also be used after any modifiers and before the specifier (here marked as z), for example:
  • %4z pad to 4 characters (with default padding character)
  • %_12z pad with spaces to 12 characters

<alternate>

An optional E character indicates an alternate formatting. Currently this only affects %Z and %z.
  • %Ez alternate formatting

<specifier>

For all types (note these three are done by formatTime, not by formatCharacter):
  • %% %
  • %t tab
  • %n newline

TimeZone

For TimeZone (and ZonedTime and UTCTime):
  • %z timezone offset in the format ±HHMM
  • %Ez timezone offset in the format ±HH:MM
  • %Z timezone name (or else offset in the format ±HHMM)
  • %EZ timezone name (or else offset in the format ±HH:MM)

LocalTime

For LocalTime (and ZonedTime and UTCTime and UniversalTime):
  • %c as dateTimeFmt locale (e.g. %a %b %e %H:%M:%S %Z %Y)

TimeOfDay

For TimeOfDay (and LocalTime and ZonedTime and UTCTime and UniversalTime):
  • %R same as %H:%M
  • %T same as %H:%M:%S
  • %X as timeFmt locale (e.g. %H:%M:%S)
  • %r as time12Fmt locale (e.g. %I:%M:%S %p)
  • %P day-half of day from (amPm locale), converted to lowercase, am, pm
  • %p day-half of day from (amPm locale), AM, PM
  • %H hour of day (24-hour), 0-padded to two chars, 00 - 23
  • %k hour of day (24-hour), space-padded to two chars, 0 - 23
  • %I hour of day-half (12-hour), 0-padded to two chars, 01 - 12
  • %l hour of day-half (12-hour), space-padded to two chars, 1 - 12
  • %M minute of hour, 0-padded to two chars, 00 - 59
  • %S second of minute (without decimal part), 0-padded to two chars, 00 - 60
  • %q picosecond of second, 0-padded to twelve chars, 000000000000 - 999999999999.
  • %Q decimal point and fraction of second, up to 12 second decimals, without trailing zeros. For a whole number of seconds, %Q omits the decimal point unless padding is specified.

UTCTime and ZonedTime

For UTCTime and ZonedTime:
  • %s number of whole seconds since the Unix epoch. For times before the Unix epoch, this is a negative number. Note that in %s.%q and %s%Q the decimals are positive, not negative. For example, 0.9 seconds before the Unix epoch is formatted as -1.1 with %s%Q.

DayOfWeek

For DayOfWeek (and Day and LocalTime and ZonedTime and UTCTime and UniversalTime):
  • %u day of week number for Week Date format, 1 (= Monday) - 7 (= Sunday)
  • %w day of week number, 0 (= Sunday) - 6 (= Saturday)
  • %a day of week, short form (snd from wDays locale), Sun - Sat
  • %A day of week, long form (fst from wDays locale), Sunday - Saturday

Month

For Month (and Day and LocalTime and ZonedTime and UTCTime and UniversalTime):
  • %Y year, no padding. Note %0Y and %_Y pad to four chars
  • %y year of century, 0-padded to two chars, 00 - 99
  • %C century, no padding. Note %0C and %_C pad to two chars
  • %B month name, long form (fst from months locale), January - December
  • %b, %h month name, short form (snd from months locale), Jan - Dec
  • %m month of year, 0-padded to two chars, 01 - 12

Day

For Day (and LocalTime and ZonedTime and UTCTime and UniversalTime):
  • %D same as %m/%d/%y
  • %F same as %Y-%m-%d
  • %x as dateFmt locale (e.g. %m/%d/%y)
  • %d day of month, 0-padded to two chars, 01 - 31
  • %e day of month, space-padded to two chars, 1 - 31
  • %j day of year, 0-padded to three chars, 001 - 366
  • %f century for Week Date format, no padding. Note %0f and %_f pad to two chars
  • %V week of year for Week Date format, 0-padded to two chars, 01 - 53
  • %U week of year where weeks start on Sunday (as sundayStartWeek), 0-padded to two chars, 00 - 53
  • %W week of year where weeks start on Monday (as mondayStartWeek), 0-padded to two chars, 00 - 53

Duration types

The specifiers for DiffTime, NominalDiffTime, CalendarDiffDays, and CalendarDiffTime are semantically separate from the other types. Specifiers on negative time differences will generally be negative (think rem rather than mod).

NominalDiffTime and DiffTime

Note that a "minute" of DiffTime is simply 60 SI seconds, rather than a minute of civil time. Use NominalDiffTime to work with civil time, ignoring any leap seconds. For NominalDiffTime and DiffTime:
  • %w total whole weeks
  • %d total whole days
  • %D whole days of week
  • %h total whole hours
  • %H whole hours of day
  • %m total whole minutes
  • %M whole minutes of hour
  • %s total whole seconds
  • %Es total seconds, with decimal point and up to <width> (default 12) decimal places, without trailing zeros. For a whole number of seconds, %Es omits the decimal point unless padding is specified.
  • %0Es total seconds, with decimal point and <width> (default 12) decimal places.
  • %S whole seconds of minute
  • %ES seconds of minute, with decimal point and up to <width> (default 12) decimal places, without trailing zeros. For a whole number of seconds, %ES omits the decimal point unless padding is specified.
  • %0ES seconds of minute as two digits, with decimal point and <width> (default 12) decimal places.

CalendarDiffDays

For CalendarDiffDays (and CalendarDiffTime):
  • %y total years
  • %b total months
  • %B months of year
  • %w total weeks, not including months
  • %d total days, not including months
  • %D days of week

CalendarDiffTime

For CalendarDiffTime:
  • %h total hours, not including months
  • %H hours of day
  • %m total minutes, not including months
  • %M minutes of hour
  • %s total whole seconds, not including months
  • %Es total seconds, not including months, with decimal point and up to <width> (default 12) decimal places, without trailing zeros. For a whole number of seconds, %Es omits the decimal point unless padding is specified.
  • %0Es total seconds, not including months, with decimal point and <width> (default 12) decimal places.
  • %S whole seconds of minute
  • %ES seconds of minute, with decimal point and up to <width> (default 12) decimal places, without trailing zeros. For a whole number of seconds, %ES omits the decimal point unless padding is specified.
  • %0ES seconds of minute as two digits, with decimal point and <width> (default 12) decimal places.
The type ForeignPtr represents references to objects that are maintained in a foreign language, i.e., that are not part of the data structures usually managed by the Haskell storage manager. The essential difference between ForeignPtrs and vanilla memory references of type Ptr a is that the former may be associated with finalizers. A finalizer is a routine that is invoked when the Haskell storage manager detects that - within the Haskell heap and stack - there are no more references left that are pointing to the ForeignPtr. Typically, the finalizer will, then, invoke routines in the foreign language that free the resources bound by the foreign object. The ForeignPtr is parameterised in the same way as Ptr. The type argument of ForeignPtr should normally be an instance of class Storable.
Forget has a polymorphic kind since 5.6.