-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Basic libraries -- -- This package contains the Prelude and its support libraries, and a -- large collection of useful libraries ranging from data structures to -- parsing combinators and debugging utilities. @package base -- | The highly unsafe primitive unsafeCoerce converts a value from -- any type to any other type. Needless to say, if you use this function, -- it is your responsibility to ensure that the old and new types have -- identical internal representations, in order to prevent runtime -- corruption. -- -- The types for which unsafeCoerce is representation-safe may -- differ from compiler to compiler (and version to version). -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Show is equivalent to -- --
-- instance (Show a) => Show (Tree a) where -- -- showsPrec d (Leaf m) = showParen (d > app_prec) $ -- showString "Leaf " . showsPrec (app_prec+1) m -- where app_prec = 10 -- -- showsPrec d (u :^: v) = showParen (d > up_prec) $ -- showsPrec (up_prec+1) u . -- showString " :^: " . -- showsPrec (up_prec+1) v -- where up_prec = 5 ---- -- Note that right-associativity of :^: is ignored. For example, -- --
-- fmap id == id -- fmap (f . g) == fmap f . fmap g ---- -- The instances of Functor for lists, Maybe and IO -- satisfy these laws. class Functor f where <$ = fmap . const fmap :: Functor f => (a -> b) -> f a -> f b -- | The Monad class defines the basic operations over a -- monad, a concept from a branch of mathematics known as -- category theory. From the perspective of a Haskell programmer, -- however, it is best to think of a monad as an abstract datatype -- of actions. Haskell's do expressions provide a convenient -- syntax for writing monadic expressions. -- -- Minimal complete definition: >>= and return. -- -- Instances of Monad should satisfy the following laws: -- --
-- return a >>= k == k a -- m >>= return == m -- m >>= (\x -> k x >>= h) == (m >>= k) >>= h ---- -- Instances of both Monad and Functor should additionally -- satisfy the law: -- --
-- fmap f xs == xs >>= return . f ---- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Monad m where m >> k = m >>= \ _ -> k fail s = error s (>>=) :: Monad m => m a -> (a -> m b) -> m b (>>) :: Monad m => m a -> m b -> m b return :: Monad m => a -> m a fail :: Monad m => String -> m a -- | Monads that also support choice and failure. class Monad m => MonadPlus m mzero :: MonadPlus m => m a mplus :: MonadPlus m => m a -> m a -> m a -- | mapM f is equivalent to sequence . -- map f. mapM :: Monad m => (a -> m b) -> [a] -> m [b] -- | mapM_ f is equivalent to sequence_ . -- map f. mapM_ :: Monad m => (a -> m b) -> [a] -> m () -- | forM is mapM with its arguments flipped forM :: Monad m => [a] -> (a -> m b) -> m [b] -- | forM_ is mapM_ with its arguments flipped forM_ :: Monad m => [a] -> (a -> m b) -> m () -- | Evaluate each action in the sequence from left to right, and collect -- the results. sequence :: Monad m => [m a] -> m [a] -- | Evaluate each action in the sequence from left to right, and ignore -- the results. sequence_ :: Monad m => [m a] -> m () -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b -- | Left-to-right Kleisli composition of monads. (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) -- | Right-to-left Kleisli composition of monads. -- (>=>), with the arguments flipped (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c) -- | forever act repeats the action infinitely. forever :: Monad m => m a -> m b -- | void value discards or ignores the result of -- evaluation, such as the return value of an IO action. void :: Functor f => f a -> f () -- | The join function is the conventional monad join operator. It -- is used to remove one level of monadic structure, projecting its bound -- argument into the outer level. join :: Monad m => m (m a) -> m a -- | This generalizes the list-based concat function. msum :: MonadPlus m => [m a] -> m a -- | Direct MonadPlus equivalent of filter -- filter = (mfilter:: (a -> Bool) -> [a] -> -- [a] applicable to any MonadPlus, for example mfilter -- odd (Just 1) == Just 1 mfilter odd (Just 2) == Nothing mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a -- | This generalizes the list-based filter function. filterM :: Monad m => (a -> m Bool) -> [a] -> m [a] -- | The mapAndUnzipM function maps its first argument over a list, -- returning the result as a pair of lists. This function is mainly used -- with complicated data structures or a state-transforming monad. mapAndUnzipM :: Monad m => (a -> m (b, c)) -> [a] -> m ([b], [c]) -- | The zipWithM function generalizes zipWith to arbitrary -- monads. zipWithM :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m [c] -- | zipWithM_ is the extension of zipWithM which ignores the -- final result. zipWithM_ :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m () -- | The foldM function is analogous to 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. -- --
-- foldM f a1 [x1, x2, ..., xm] ---- -- == -- --
-- do -- a2 <- f a1 x1 -- a3 <- f a2 x2 -- ... -- f am xm ---- -- If right-to-left evaluation is required, the input list should be -- reversed. foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a -- | Like foldM, but discards the result. foldM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m () -- | replicateM n act performs the action n times, -- gathering the results. replicateM :: Monad m => Int -> m a -> m [a] -- | Like replicateM, but discards the result. replicateM_ :: Monad m => Int -> m a -> m () -- | guard b is return () if b is -- True, and mzero if b is False. guard :: MonadPlus m => Bool -> m () -- | Conditional execution of monadic expressions. For example, -- --
-- when debug (putStr "Debugging\n") ---- -- will output the string Debugging\n if the Boolean value -- debug is True, and otherwise do nothing. when :: Monad m => Bool -> m () -> m () -- | The reverse of when. unless :: Monad m => Bool -> m () -> m () -- | Promote a function to a monad. liftM :: Monad m => (a1 -> r) -> m a1 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right. For example, -- --
-- liftM2 (+) [0,1] [0,2] = [0,2,1,3] -- liftM2 (+) (Just 1) Nothing = Nothing --liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r -- | In many situations, the liftM operations can be replaced by -- uses of ap, which promotes function application. -- --
-- return f `ap` x1 `ap` ... `ap` xn ---- -- is equivalent to -- --
-- liftMn f x1 x2 ... xn --ap :: Monad m => m (a -> b) -> m a -> m b instance MonadPlus Maybe instance MonadPlus [] -- | Marshalling support. Unsafe API. module Foreign.Marshal.Unsafe -- | Sometimes an external entity is a pure function, except that it passes -- arguments and/or results via pointers. The function -- unsafeLocalState permits the packaging of such entities as -- pure functions. -- -- The only IO operations allowed in the IO action passed to -- unsafeLocalState are (a) local allocation (alloca, -- allocaBytes and derived operations such as withArray -- and withCString), and (b) pointer operations -- (Foreign.Storable and Foreign.Ptr) on the pointers -- to local storage, and (c) foreign functions whose only observable -- effect is to read and/or write the locally allocated memory. Passing -- an IO operation that does not obey these rules results in undefined -- behaviour. -- -- It is expected that this operation will be replaced in a future -- revision of Haskell. unsafeLocalState :: IO a -> a -- | This module defines bitwise operations for signed and unsigned -- integers. Instances of the class Bits for the Int and -- Integer types are available from this module, and instances for -- explicitly sized integral types are available from the Data.Int -- and Data.Word modules. module Data.Bits -- | The Bits class defines bitwise operations over integral types. -- --
-- floatToDigits base x = ([d1,d2,...,dn], e) ---- -- then -- --
n >= 1
x = 0.d1d2...dn * (base**e)
0 <= di <= base-1
-- sp == castPtrToStablePtr (castStablePtrToPtr sp) ---- -- for any stable pointer sp on which freeStablePtr has -- not been executed yet. Moreover, castPtrToStablePtr may only be -- applied to pointers that have been produced by -- castStablePtrToPtr. castPtrToStablePtr :: Ptr () -> StablePtr a -- | Type classes for I/O providers. module GHC.IO.Device -- | A low-level I/O provider where the data is bytes in memory. class RawIO a read :: RawIO a => a -> Ptr Word8 -> Int -> IO Int readNonBlocking :: RawIO a => a -> Ptr Word8 -> Int -> IO (Maybe Int) write :: RawIO a => a -> Ptr Word8 -> Int -> IO () writeNonBlocking :: RawIO a => a -> Ptr Word8 -> Int -> IO Int -- | I/O operations required for implementing a Handle. class IODevice a where isTerminal _ = return False isSeekable _ = return False seek _ _ _ = ioe_unsupportedOperation tell _ = ioe_unsupportedOperation getSize _ = ioe_unsupportedOperation setSize _ _ = ioe_unsupportedOperation setEcho _ _ = ioe_unsupportedOperation getEcho _ = ioe_unsupportedOperation setRaw _ _ = ioe_unsupportedOperation dup _ = ioe_unsupportedOperation dup2 _ _ = ioe_unsupportedOperation ready :: IODevice a => a -> Bool -> Int -> IO Bool close :: IODevice a => a -> IO () isTerminal :: IODevice a => a -> IO Bool isSeekable :: IODevice a => a -> IO Bool seek :: IODevice a => a -> SeekMode -> Integer -> IO () tell :: IODevice a => a -> IO Integer getSize :: IODevice a => a -> IO Integer setSize :: IODevice a => a -> Integer -> IO () setEcho :: IODevice a => a -> Bool -> IO () getEcho :: IODevice a => a -> IO Bool setRaw :: IODevice a => a -> Bool -> IO () devType :: IODevice a => a -> IO IODeviceType dup :: IODevice a => a -> IO a dup2 :: IODevice a => a -> a -> IO a -- | Type of a device that can be used to back a Handle (see also -- mkFileHandle). The standard libraries provide creation of -- Handles via Posix file operations with file descriptors (see -- mkHandleFromFD) with FD being the underlying IODevice -- instance. -- -- Users may provide custom instances of IODevice which are -- expected to conform the following rules: data IODeviceType -- | The standard libraries do not have direct support for this device -- type, but a user implementation is expected to provide a list of file -- names in the directory, in any order, separated by '\0' -- characters, excluding the . and .. -- names. See also getDirectoryContents. Seek operations are not -- supported on directories (other than to the zero position). Directory :: IODeviceType -- | A duplex communications channel (results in creation of a duplex -- Handle). The standard libraries use this device type when -- creating Handles for open sockets. Stream :: IODeviceType -- | A file that may be read or written, and also may be seekable. RegularFile :: IODeviceType -- | A raw (disk) device which supports block binary read and write -- operations and may be seekable only to positions of certain -- granularity (block- aligned). RawDevice :: IODeviceType -- | A mode that determines the effect of hSeek hdl mode -- i. data SeekMode -- | the position of hdl is set to i. AbsoluteSeek :: SeekMode -- | the position of hdl is set to offset i from the -- current position. RelativeSeek :: SeekMode -- | the position of hdl is set to offset i from the end -- of the file. SeekFromEnd :: SeekMode instance Eq IODeviceType instance Eq SeekMode instance Ord SeekMode instance Ix SeekMode instance Enum SeekMode instance Read SeekMode instance Show SeekMode -- | The module Foreign.Storable provides most elementary support -- for marshalling and is part of the language-independent portion of the -- Foreign Function Interface (FFI), and will normally be imported via -- the Foreign module. module Foreign.Storable -- | The member functions of this class facilitate writing values of -- primitive types to raw memory (which may have been allocated with the -- above mentioned routines) and reading values from blocks of raw -- memory. The class, furthermore, includes support for computing the -- storage requirements and alignment restrictions of storable types. -- -- Memory addresses are represented as values of type Ptr -- a, for some a which is an instance of class -- Storable. The type argument to Ptr helps provide some -- valuable type safety in FFI code (you can't mix pointers of different -- types without an explicit cast), while helping the Haskell type system -- figure out which marshalling method is needed for a given pointer. -- -- All marshalling between Haskell and a foreign language ultimately -- boils down to translating Haskell data structures into the binary -- representation of a corresponding data structure of the foreign -- language and vice versa. To code this marshalling in Haskell, it is -- necessary to manipulate primitive data types stored in unstructured -- memory blocks. The class Storable facilitates this manipulation -- on all types for which it is instantiated, which are the standard -- basic types of Haskell, the fixed size Int types -- (Int8, Int16, Int32, Int64), the fixed -- size Word types (Word8, Word16, Word32, -- Word64), StablePtr, all types from -- Foreign.C.Types, as well as Ptr. -- -- Minimal complete definition: sizeOf, alignment, one of -- peek, peekElemOff and peekByteOff, and one of -- poke, pokeElemOff and pokeByteOff. class Storable a where peekElemOff = peekElemOff_ undefined where peekElemOff_ :: a -> Ptr a -> Int -> IO a peekElemOff_ undef ptr off = peekByteOff ptr (off * sizeOf undef) pokeElemOff ptr off val = pokeByteOff ptr (off * sizeOf val) val peekByteOff ptr off = peek (ptr `plusPtr` off) pokeByteOff ptr off = poke (ptr `plusPtr` off) peek ptr = peekElemOff ptr 0 poke ptr = pokeElemOff ptr 0 sizeOf :: Storable a => a -> Int alignment :: Storable a => a -> Int peekElemOff :: Storable a => Ptr a -> Int -> IO a pokeElemOff :: Storable a => Ptr a -> Int -> a -> IO () peekByteOff :: Storable a => Ptr b -> Int -> IO a pokeByteOff :: Storable a => Ptr b -> Int -> a -> IO () peek :: Storable a => Ptr a -> IO a poke :: Storable a => Ptr a -> a -> IO () instance Storable Fingerprint instance Storable Int64 instance Storable Int32 instance Storable Int16 instance Storable Int8 instance Storable Word64 instance Storable Word32 instance Storable Word16 instance Storable Word8 instance Storable Double instance Storable Float instance Storable (StablePtr a) instance Storable (FunPtr a) instance Storable (Ptr a) instance Storable Word instance Storable Int instance Storable Char instance Storable Bool -- | Mapping of C types to corresponding Haskell types. module Foreign.C.Types -- | Haskell type representing the C char type. newtype CChar CChar :: Int8 -> CChar -- | Haskell type representing the C signed char type. newtype CSChar CSChar :: Int8 -> CSChar -- | Haskell type representing the C unsigned char type. newtype CUChar CUChar :: Word8 -> CUChar -- | Haskell type representing the C short type. newtype CShort CShort :: Int16 -> CShort -- | Haskell type representing the C unsigned short type. newtype CUShort CUShort :: Word16 -> CUShort -- | Haskell type representing the C int type. newtype CInt CInt :: Int32 -> CInt -- | Haskell type representing the C unsigned int type. newtype CUInt CUInt :: Word32 -> CUInt -- | Haskell type representing the C long type. newtype CLong CLong :: Int64 -> CLong -- | Haskell type representing the C unsigned long type. newtype CULong CULong :: Word64 -> CULong -- | Haskell type representing the C ptrdiff_t type. newtype CPtrdiff CPtrdiff :: Int64 -> CPtrdiff -- | Haskell type representing the C size_t type. newtype CSize CSize :: Word64 -> CSize -- | Haskell type representing the C wchar_t type. newtype CWchar CWchar :: Int32 -> CWchar -- | Haskell type representing the C sig_atomic_t type. newtype CSigAtomic CSigAtomic :: Int32 -> CSigAtomic -- | Haskell type representing the C long long type. newtype CLLong CLLong :: Int64 -> CLLong -- | Haskell type representing the C unsigned long long type. newtype CULLong CULLong :: Word64 -> CULLong newtype CIntPtr CIntPtr :: Int64 -> CIntPtr newtype CUIntPtr CUIntPtr :: Word64 -> CUIntPtr newtype CIntMax CIntMax :: Int64 -> CIntMax newtype CUIntMax CUIntMax :: Word64 -> CUIntMax -- | Haskell type representing the C clock_t type. newtype CClock CClock :: Int64 -> CClock -- | Haskell type representing the C time_t type. newtype CTime CTime :: Int64 -> CTime -- | Haskell type representing the C useconds_t type. newtype CUSeconds CUSeconds :: Word32 -> CUSeconds -- | Haskell type representing the C suseconds_t type. newtype CSUSeconds CSUSeconds :: Int64 -> CSUSeconds -- | Haskell type representing the C float type. newtype CFloat CFloat :: Float -> CFloat -- | Haskell type representing the C double type. newtype CDouble CDouble :: Double -> CDouble -- | Haskell type representing the C FILE type. data CFile -- | Haskell type representing the C fpos_t type. data CFpos -- | Haskell type representing the C jmp_buf type. data CJmpBuf instance Typeable CUIntMax instance Typeable CIntMax instance Typeable CUIntPtr instance Typeable CIntPtr instance Typeable CSUSeconds instance Typeable CUSeconds instance Typeable CTime instance Typeable CClock instance Typeable CSigAtomic instance Typeable CWchar instance Typeable CSize instance Typeable CPtrdiff instance Typeable CDouble instance Typeable CFloat instance Typeable CULLong instance Typeable CLLong instance Typeable CULong instance Typeable CLong instance Typeable CUInt instance Typeable CInt instance Typeable CUShort instance Typeable CShort instance Typeable CUChar instance Typeable CSChar instance Typeable CChar instance Eq CChar instance Ord CChar instance Num CChar instance Enum CChar instance Storable CChar instance Real CChar instance Bounded CChar instance Integral CChar instance Bits CChar instance Eq CSChar instance Ord CSChar instance Num CSChar instance Enum CSChar instance Storable CSChar instance Real CSChar instance Bounded CSChar instance Integral CSChar instance Bits CSChar instance Eq CUChar instance Ord CUChar instance Num CUChar instance Enum CUChar instance Storable CUChar instance Real CUChar instance Bounded CUChar instance Integral CUChar instance Bits CUChar instance Eq CShort instance Ord CShort instance Num CShort instance Enum CShort instance Storable CShort instance Real CShort instance Bounded CShort instance Integral CShort instance Bits CShort instance Eq CUShort instance Ord CUShort instance Num CUShort instance Enum CUShort instance Storable CUShort instance Real CUShort instance Bounded CUShort instance Integral CUShort instance Bits CUShort instance Eq CInt instance Ord CInt instance Num CInt instance Enum CInt instance Storable CInt instance Real CInt instance Bounded CInt instance Integral CInt instance Bits CInt instance Eq CUInt instance Ord CUInt instance Num CUInt instance Enum CUInt instance Storable CUInt instance Real CUInt instance Bounded CUInt instance Integral CUInt instance Bits CUInt instance Eq CLong instance Ord CLong instance Num CLong instance Enum CLong instance Storable CLong instance Real CLong instance Bounded CLong instance Integral CLong instance Bits CLong instance Eq CULong instance Ord CULong instance Num CULong instance Enum CULong instance Storable CULong instance Real CULong instance Bounded CULong instance Integral CULong instance Bits CULong instance Eq CLLong instance Ord CLLong instance Num CLLong instance Enum CLLong instance Storable CLLong instance Real CLLong instance Bounded CLLong instance Integral CLLong instance Bits CLLong instance Eq CULLong instance Ord CULLong instance Num CULLong instance Enum CULLong instance Storable CULLong instance Real CULLong instance Bounded CULLong instance Integral CULLong instance Bits CULLong instance Eq CFloat instance Ord CFloat instance Num CFloat instance Enum CFloat instance Storable CFloat instance Real CFloat instance Fractional CFloat instance Floating CFloat instance RealFrac CFloat instance RealFloat CFloat instance Eq CDouble instance Ord CDouble instance Num CDouble instance Enum CDouble instance Storable CDouble instance Real CDouble instance Fractional CDouble instance Floating CDouble instance RealFrac CDouble instance RealFloat CDouble instance Eq CPtrdiff instance Ord CPtrdiff instance Num CPtrdiff instance Enum CPtrdiff instance Storable CPtrdiff instance Real CPtrdiff instance Bounded CPtrdiff instance Integral CPtrdiff instance Bits CPtrdiff instance Eq CSize instance Ord CSize instance Num CSize instance Enum CSize instance Storable CSize instance Real CSize instance Bounded CSize instance Integral CSize instance Bits CSize instance Eq CWchar instance Ord CWchar instance Num CWchar instance Enum CWchar instance Storable CWchar instance Real CWchar instance Bounded CWchar instance Integral CWchar instance Bits CWchar instance Eq CSigAtomic instance Ord CSigAtomic instance Num CSigAtomic instance Enum CSigAtomic instance Storable CSigAtomic instance Real CSigAtomic instance Bounded CSigAtomic instance Integral CSigAtomic instance Bits CSigAtomic instance Eq CClock instance Ord CClock instance Num CClock instance Enum CClock instance Storable CClock instance Real CClock instance Eq CTime instance Ord CTime instance Num CTime instance Enum CTime instance Storable CTime instance Real CTime instance Eq CUSeconds instance Ord CUSeconds instance Num CUSeconds instance Enum CUSeconds instance Storable CUSeconds instance Real CUSeconds instance Eq CSUSeconds instance Ord CSUSeconds instance Num CSUSeconds instance Enum CSUSeconds instance Storable CSUSeconds instance Real CSUSeconds instance Eq CIntPtr instance Ord CIntPtr instance Num CIntPtr instance Enum CIntPtr instance Storable CIntPtr instance Real CIntPtr instance Bounded CIntPtr instance Integral CIntPtr instance Bits CIntPtr instance Eq CUIntPtr instance Ord CUIntPtr instance Num CUIntPtr instance Enum CUIntPtr instance Storable CUIntPtr instance Real CUIntPtr instance Bounded CUIntPtr instance Integral CUIntPtr instance Bits CUIntPtr instance Eq CIntMax instance Ord CIntMax instance Num CIntMax instance Enum CIntMax instance Storable CIntMax instance Real CIntMax instance Bounded CIntMax instance Integral CIntMax instance Bits CIntMax instance Eq CUIntMax instance Ord CUIntMax instance Num CUIntMax instance Enum CUIntMax instance Storable CUIntMax instance Real CUIntMax instance Bounded CUIntMax instance Integral CUIntMax instance Bits CUIntMax instance Show CUIntMax instance Read CUIntMax instance Show CIntMax instance Read CIntMax instance Show CUIntPtr instance Read CUIntPtr instance Show CIntPtr instance Read CIntPtr instance Show CSUSeconds instance Read CSUSeconds instance Show CUSeconds instance Read CUSeconds instance Show CTime instance Read CTime instance Show CClock instance Read CClock instance Show CSigAtomic instance Read CSigAtomic instance Show CWchar instance Read CWchar instance Show CSize instance Read CSize instance Show CPtrdiff instance Read CPtrdiff instance Show CDouble instance Read CDouble instance Show CFloat instance Read CFloat instance Show CULLong instance Read CULLong instance Show CLLong instance Read CLLong instance Show CULong instance Read CULong instance Show CLong instance Read CLong instance Show CUInt instance Read CUInt instance Show CInt instance Read CInt instance Show CUShort instance Read CUShort instance Show CShort instance Read CShort instance Show CUChar instance Read CUChar instance Show CSChar instance Read CSChar instance Show CChar instance Read CChar -- | The Char type and associated operations. module Data.Char -- | The character type Char is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) characters (see -- http://www.unicode.org/ for details). This set extends the ISO -- 8859-1 (Latin-1) character set (the first 256 characters), which is -- itself an extension of the ASCII character set (the first 128 -- characters). A character literal in Haskell has type Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char :: * -- | Selects control characters, which are the non-printing characters of -- the Latin-1 subset of Unicode. isControl :: Char -> Bool -- | Returns True for any Unicode space character, and the control -- characters \t, \n, \r, \f, -- \v. isSpace :: Char -> Bool -- | Selects lower-case alphabetic Unicode characters (letters). isLower :: Char -> Bool -- | Selects upper-case or title-case alphabetic Unicode characters -- (letters). Title case is used by a small number of letter ligatures -- like the single-character form of Lj. isUpper :: Char -> Bool -- | Selects alphabetic Unicode characters (lower-case, upper-case and -- title-case letters, plus letters of caseless scripts and modifiers -- letters). This function is equivalent to isLetter. isAlpha :: Char -> Bool -- | Selects alphabetic or numeric digit Unicode characters. -- -- Note that numeric digits outside the ASCII range are selected by this -- function but not by isDigit. Such digits may be part of -- identifiers but are not used by the printer and reader to represent -- numbers. isAlphaNum :: Char -> Bool -- | Selects printable Unicode characters (letters, numbers, marks, -- punctuation, symbols and spaces). isPrint :: Char -> Bool -- | Selects ASCII digits, i.e. '0'..'9'. isDigit :: Char -> Bool -- | Selects ASCII octal digits, i.e. '0'..'7'. isOctDigit :: Char -> Bool -- | Selects ASCII hexadecimal digits, i.e. '0'..'9', -- 'a'..'f', 'A'..'F'. isHexDigit :: Char -> Bool -- | Selects alphabetic Unicode characters (lower-case, upper-case and -- title-case letters, plus letters of caseless scripts and modifiers -- letters). This function is equivalent to isAlpha. isLetter :: Char -> Bool -- | Selects Unicode mark characters, e.g. accents and the like, which -- combine with preceding letters. isMark :: Char -> Bool -- | Selects Unicode numeric characters, including digits from various -- scripts, Roman numerals, etc. isNumber :: Char -> Bool -- | Selects Unicode punctuation characters, including various kinds of -- connectors, brackets and quotes. isPunctuation :: Char -> Bool -- | Selects Unicode symbol characters, including mathematical and currency -- symbols. isSymbol :: Char -> Bool -- | Selects Unicode space and separator characters. isSeparator :: Char -> Bool -- | Selects the first 128 characters of the Unicode character set, -- corresponding to the ASCII character set. isAscii :: Char -> Bool -- | Selects the first 256 characters of the Unicode character set, -- corresponding to the ISO 8859-1 (Latin-1) character set. isLatin1 :: Char -> Bool -- | Selects ASCII upper-case letters, i.e. characters satisfying both -- isAscii and isUpper. isAsciiUpper :: Char -> Bool -- | Selects ASCII lower-case letters, i.e. characters satisfying both -- isAscii and isLower. isAsciiLower :: Char -> Bool -- | Unicode General Categories (column 2 of the UnicodeData table) in the -- order they are listed in the Unicode standard. data GeneralCategory -- | Lu: Letter, Uppercase UppercaseLetter :: GeneralCategory -- | Ll: Letter, Lowercase LowercaseLetter :: GeneralCategory -- | Lt: Letter, Titlecase TitlecaseLetter :: GeneralCategory -- | Lm: Letter, Modifier ModifierLetter :: GeneralCategory -- | Lo: Letter, Other OtherLetter :: GeneralCategory -- | Mn: Mark, Non-Spacing NonSpacingMark :: GeneralCategory -- | Mc: Mark, Spacing Combining SpacingCombiningMark :: GeneralCategory -- | Me: Mark, Enclosing EnclosingMark :: GeneralCategory -- | Nd: Number, Decimal DecimalNumber :: GeneralCategory -- | Nl: Number, Letter LetterNumber :: GeneralCategory -- | No: Number, Other OtherNumber :: GeneralCategory -- | Pc: Punctuation, Connector ConnectorPunctuation :: GeneralCategory -- | Pd: Punctuation, Dash DashPunctuation :: GeneralCategory -- | Ps: Punctuation, Open OpenPunctuation :: GeneralCategory -- | Pe: Punctuation, Close ClosePunctuation :: GeneralCategory -- | Pi: Punctuation, Initial quote InitialQuote :: GeneralCategory -- | Pf: Punctuation, Final quote FinalQuote :: GeneralCategory -- | Po: Punctuation, Other OtherPunctuation :: GeneralCategory -- | Sm: Symbol, Math MathSymbol :: GeneralCategory -- | Sc: Symbol, Currency CurrencySymbol :: GeneralCategory -- | Sk: Symbol, Modifier ModifierSymbol :: GeneralCategory -- | So: Symbol, Other OtherSymbol :: GeneralCategory -- | Zs: Separator, Space Space :: GeneralCategory -- | Zl: Separator, Line LineSeparator :: GeneralCategory -- | Zp: Separator, Paragraph ParagraphSeparator :: GeneralCategory -- | Cc: Other, Control Control :: GeneralCategory -- | Cf: Other, Format Format :: GeneralCategory -- | Cs: Other, Surrogate Surrogate :: GeneralCategory -- | Co: Other, Private Use PrivateUse :: GeneralCategory -- | Cn: Other, Not Assigned NotAssigned :: GeneralCategory -- | The Unicode general category of the character. generalCategory :: Char -> GeneralCategory -- | Convert a letter to the corresponding upper-case letter, if any. Any -- other character is returned unchanged. toUpper :: Char -> Char -- | Convert a letter to the corresponding lower-case letter, if any. Any -- other character is returned unchanged. toLower :: Char -> Char -- | Convert a letter to the corresponding title-case or upper-case letter, -- if any. (Title case differs from upper case only for a small number of -- ligature letters.) Any other character is returned unchanged. toTitle :: Char -> Char -- | Convert a single digit Char to the corresponding Int. -- This function fails unless its argument satisfies isHexDigit, -- but recognises both upper and lower-case hexadecimal digits (i.e. -- '0'..'9', 'a'..'f', -- 'A'..'F'). digitToInt :: Char -> Int -- | Convert an Int in the range 0..15 to the -- corresponding single digit Char. This function fails on other -- inputs, and generates lower-case hexadecimal digits. intToDigit :: Int -> Char -- | The fromEnum method restricted to the type Char. ord :: Char -> Int -- | The toEnum method restricted to the type Char. chr :: Int -> Char -- | Convert a character to a string using only printable characters, using -- Haskell source-language escape conventions. For example: -- --
-- showLitChar '\n' s = "\\n" ++ s --showLitChar :: Char -> ShowS -- | Read a string representation of a character, using Haskell -- source-language escape conventions. For example: -- --
-- lexLitChar "\\nHello" = [("\\n", "Hello")] --lexLitChar :: ReadS String -- | Read a string representation of a character, using Haskell -- source-language escape conventions, and convert it to the character -- that it encodes. For example: -- --
-- readLitChar "\\nHello" = [('\n', "Hello")] --readLitChar :: ReadS Char instance Eq GeneralCategory instance Ord GeneralCategory instance Enum GeneralCategory instance Read GeneralCategory instance Show GeneralCategory instance Bounded GeneralCategory instance Ix GeneralCategory -- | Operations on lists. module Data.List -- | Append two lists, i.e., -- --
-- [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] -- [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...] ---- -- If the first list is not finite, the result is the first list. (++) :: [a] -> [a] -> [a] -- | Extract the first element of a list, which must be non-empty. head :: [a] -> a -- | Extract the last element of a list, which must be finite and -- non-empty. last :: [a] -> a -- | Extract the elements after the head of a list, which must be -- non-empty. tail :: [a] -> [a] -- | Return all the elements of a list except the last one. The list must -- be non-empty. init :: [a] -> [a] -- | Test whether a list is empty. null :: [a] -> Bool -- | O(n). length returns the length of a finite list as an -- Int. It is an instance of the more general -- genericLength, the result type of which may be any kind of -- number. length :: [a] -> Int -- | map f xs is the list obtained by applying f -- to each element of xs, i.e., -- --
-- map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] -- map f [x1, x2, ...] == [f x1, f x2, ...] --map :: (a -> b) -> [a] -> [b] -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. reverse :: [a] -> [a] -- | The intersperse function takes an element and a list and -- `intersperses' that element between the elements of the list. For -- example, -- --
-- intersperse ',' "abcde" == "a,b,c,d,e" --intersperse :: a -> [a] -> [a] -- | intercalate xs xss is equivalent to (concat -- (intersperse xs xss)). It inserts the list xs in -- between the lists in xss and concatenates the result. intercalate :: [a] -> [[a]] -> [a] -- | The transpose function transposes the rows and columns of its -- argument. For example, -- --
-- transpose [[1,2,3],[4,5,6]] == [[1,4],[2,5],[3,6]] --transpose :: [[a]] -> [[a]] -- | The subsequences function returns the list of all subsequences -- of the argument. -- --
-- subsequences "abc" == ["","a","b","ab","c","ac","bc","abc"] --subsequences :: [a] -> [[a]] -- | The permutations function returns the list of all permutations -- of the argument. -- --
-- permutations "abc" == ["abc","bac","cba","bca","cab","acb"] --permutations :: [a] -> [[a]] -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a list, reduces the -- list using the binary operator, from left to right: -- --
-- foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn ---- -- The list must be finite. foldl :: (a -> b -> a) -> a -> [b] -> a -- | A strict version of foldl. foldl' :: (a -> b -> a) -> a -> [b] -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty lists. foldl1 :: (a -> a -> a) -> [a] -> a -- | A strict version of foldl1 foldl1' :: (a -> a -> a) -> [a] -> a -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a list, reduces -- the list using the binary operator, from right to left: -- --
-- foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) --foldr :: (a -> b -> b) -> b -> [a] -> b -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty lists. foldr1 :: (a -> a -> a) -> [a] -> a -- | Concatenate a list of lists. concat :: [[a]] -> [a] -- | Map a function over a list and concatenate the results. concatMap :: (a -> [b]) -> [a] -> [b] -- | and returns the conjunction of a Boolean list. For the result -- to be True, the list must be finite; False, however, -- results from a False value at a finite index of a finite or -- infinite list. and :: [Bool] -> Bool -- | or returns the disjunction of a Boolean list. For the result to -- be False, the list must be finite; True, however, -- results from a True value at a finite index of a finite or -- infinite list. or :: [Bool] -> Bool -- | Applied to a predicate and a list, any determines if any -- element of the list satisfies the predicate. For the result to be -- False, the list must be finite; True, however, results -- from a True value for the predicate applied to an element at a -- finite index of a finite or infinite list. any :: (a -> Bool) -> [a] -> Bool -- | Applied to a predicate and a list, all determines if all -- elements of the list satisfy the predicate. For the result to be -- True, the list must be finite; False, however, results -- from a False value for the predicate applied to an element at a -- finite index of a finite or infinite list. all :: (a -> Bool) -> [a] -> Bool -- | The sum function computes the sum of a finite list of numbers. sum :: Num a => [a] -> a -- | The product function computes the product of a finite list of -- numbers. product :: Num a => [a] -> a -- | maximum returns the maximum value from a list, which must be -- non-empty, finite, and of an ordered type. It is a special case of -- maximumBy, which allows the programmer to supply their own -- comparison function. maximum :: Ord a => [a] -> a -- | minimum returns the minimum value from a list, which must be -- non-empty, finite, and of an ordered type. It is a special case of -- minimumBy, which allows the programmer to supply their own -- comparison function. minimum :: Ord a => [a] -> a -- | scanl is similar to foldl, but returns a list of -- successive reduced values from the left: -- --
-- scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...] ---- -- Note that -- --
-- last (scanl f z xs) == foldl f z xs. --scanl :: (a -> b -> a) -> a -> [b] -> [a] -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
-- scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...] --scanl1 :: (a -> a -> a) -> [a] -> [a] -- | scanr is the right-to-left dual of scanl. Note that -- --
-- head (scanr f z xs) == foldr f z xs. --scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (a -> a -> a) -> [a] -> [a] -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a list, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new list. mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a list, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new list. mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) -- | iterate f x returns an infinite list of repeated -- applications of f to x: -- --
-- iterate f x == [x, f x, f (f x), ...] --iterate :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. repeat :: a -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. replicate :: Int -> a -> [a] -- | cycle ties a finite list into a circular one, or equivalently, -- the infinite repetition of the original list. It is the identity on -- infinite lists. cycle :: [a] -> [a] -- | The unfoldr function is a `dual' to foldr: while -- foldr reduces a list to a summary value, unfoldr builds -- a list from a seed value. The function takes the element and returns -- Nothing if it is done producing the list or returns Just -- (a,b), in which case, a is a prepended to the list -- and b is used as the next element in a recursive call. For -- example, -- --
-- iterate f == unfoldr (\x -> Just (x, f x)) ---- -- In some cases, unfoldr can undo a foldr operation: -- --
-- unfoldr f' (foldr f z xs) == xs ---- -- if the following holds: -- --
-- f' (f x y) = Just (x,y) -- f' z = Nothing ---- -- A simple use of unfoldr: -- --
-- unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10 -- [10,9,8,7,6,5,4,3,2,1] --unfoldr :: (b -> Maybe (a, b)) -> b -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n > length xs: -- --
-- take 5 "Hello World!" == "Hello" -- take 3 [1,2,3,4,5] == [1,2,3] -- take 3 [1,2] == [1,2] -- take 3 [] == [] -- take (-1) [1,2] == [] -- take 0 [1,2] == [] ---- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. take :: Int -> [a] -> [a] -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n > length -- xs: -- --
-- drop 6 "Hello World!" == "World!" -- drop 3 [1,2,3,4,5] == [4,5] -- drop 3 [1,2] == [] -- drop 3 [] == [] -- drop (-1) [1,2] == [1,2] -- drop 0 [1,2] == [1,2] ---- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. drop :: Int -> [a] -> [a] -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
-- splitAt 6 "Hello World!" == ("Hello ","World!") -- splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) -- splitAt 1 [1,2,3] == ([1],[2,3]) -- splitAt 3 [1,2,3] == ([1,2,3],[]) -- splitAt 4 [1,2,3] == ([1,2,3],[]) -- splitAt 0 [1,2,3] == ([],[1,2,3]) -- splitAt (-1) [1,2,3] == ([],[1,2,3]) ---- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) -- | takeWhile, applied to a predicate p and a list -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p: -- --
-- takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] -- takeWhile (< 9) [1,2,3] == [1,2,3] -- takeWhile (< 0) [1,2,3] == [] --takeWhile :: (a -> Bool) -> [a] -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs: -- --
-- dropWhile (< 3) [1,2,3,4,5,1,2,3] == [3,4,5,1,2,3] -- dropWhile (< 9) [1,2,3] == [] -- dropWhile (< 0) [1,2,3] == [1,2,3] --dropWhile :: (a -> Bool) -> [a] -> [a] -- | The dropWhileEnd function drops the largest suffix of a list in -- which the given predicate holds for all elements. For example: -- --
-- dropWhileEnd isSpace "foo\n" == "foo" -- dropWhileEnd isSpace "foo bar" == "foo bar" -- dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined --dropWhileEnd :: (a -> Bool) -> [a] -> [a] -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is longest prefix (possibly empty) -- of xs of elements that satisfy p and second element -- is the remainder of the list: -- --
-- span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) -- span (< 9) [1,2,3] == ([1,2,3],[]) -- span (< 0) [1,2,3] == ([],[1,2,3]) ---- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | break, applied to a predicate p and a list -- xs, returns a tuple where first element is longest prefix -- (possibly empty) of xs of elements that do not satisfy -- p and second element is the remainder of the list: -- --
-- break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) -- break (< 9) [1,2,3] == ([],[1,2,3]) -- break (> 9) [1,2,3] == ([1,2,3],[]) ---- -- break p is equivalent to span (not . -- p). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | The stripPrefix function drops the given prefix from a list. It -- returns Nothing if the list did not start with the prefix -- given, or Just the list after the prefix, if it does. -- --
-- stripPrefix "foo" "foobar" == Just "bar" -- stripPrefix "foo" "foo" == Just "" -- stripPrefix "foo" "barfoo" == Nothing -- stripPrefix "foo" "barfoobaz" == Nothing --stripPrefix :: Eq a => [a] -> [a] -> Maybe [a] -- | The group function takes a list and returns a list of lists -- such that the concatenation of the result is equal to the argument. -- Moreover, each sublist in the result contains only equal elements. For -- example, -- --
-- group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"] ---- -- It is a special case of groupBy, which allows the programmer to -- supply their own equality test. group :: Eq a => [a] -> [[a]] -- | The inits function returns all initial segments of the -- argument, shortest first. For example, -- --
-- inits "abc" == ["","a","ab","abc"] ---- -- Note that inits has the following strictness property: -- inits _|_ = [] : _|_ inits :: [a] -> [[a]] -- | The tails function returns all final segments of the argument, -- longest first. For example, -- --
-- tails "abc" == ["abc", "bc", "c",""] ---- -- Note that tails has the following strictness property: -- tails _|_ = _|_ : _|_ tails :: [a] -> [[a]] -- | The isPrefixOf function takes two lists and returns True -- iff the first list is a prefix of the second. isPrefixOf :: Eq a => [a] -> [a] -> Bool -- | The isSuffixOf function takes two lists and returns True -- iff the first list is a suffix of the second. Both lists must be -- finite. isSuffixOf :: Eq a => [a] -> [a] -> Bool -- | The isInfixOf function takes two lists and returns True -- iff the first list is contained, wholly and intact, anywhere within -- the second. -- -- Example: -- --
-- isInfixOf "Haskell" "I really like Haskell." == True -- isInfixOf "Ial" "I really like Haskell." == False --isInfixOf :: Eq a => [a] -> [a] -> Bool -- | elem is the list membership predicate, usually written in infix -- form, e.g., x `elem` xs. For the result to be False, -- the list must be finite; True, however, results from an element -- equal to x found at a finite index of a finite or infinite -- list. elem :: Eq a => a -> [a] -> Bool -- | notElem is the negation of elem. notElem :: Eq a => a -> [a] -> Bool -- | lookup key assocs looks up a key in an association -- list. lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | The find function takes a predicate and a list and returns the -- first element in the list matching the predicate, or Nothing if -- there is no such element. find :: (a -> Bool) -> [a] -> Maybe a -- | filter, applied to a predicate and a list, returns the list of -- those elements that satisfy the predicate; i.e., -- --
-- filter p xs = [ x | x <- xs, p x] --filter :: (a -> Bool) -> [a] -> [a] -- | The partition function takes a predicate a list and returns the -- pair of lists of elements which do and do not satisfy the predicate, -- respectively; i.e., -- --
-- partition p xs == (filter p xs, filter (not . p) xs) --partition :: (a -> Bool) -> [a] -> ([a], [a]) -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. (!!) :: [a] -> Int -> a -- | The elemIndex function returns the index of the first element -- in the given list which is equal (by ==) to the query element, -- or Nothing if there is no such element. elemIndex :: Eq a => a -> [a] -> Maybe Int -- | The elemIndices function extends elemIndex, by returning -- the indices of all elements equal to the query element, in ascending -- order. elemIndices :: Eq a => a -> [a] -> [Int] -- | The findIndex function takes a predicate and a list and returns -- the index of the first element in the list satisfying the predicate, -- or Nothing if there is no such element. findIndex :: (a -> Bool) -> [a] -> Maybe Int -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. findIndices :: (a -> Bool) -> [a] -> [Int] -- | zip takes two lists and returns a list of corresponding pairs. -- If one input list is short, excess elements of the longer list are -- discarded. zip :: [a] -> [b] -> [(a, b)] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] -- | The zip4 function takes four lists and returns a list of -- quadruples, analogous to zip. zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)] -- | The zip5 function takes five lists and returns a list of -- five-tuples, analogous to zip. zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)] -- | The zip6 function takes six lists and returns a list of -- six-tuples, analogous to zip. zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)] -- | The zip7 function takes seven lists and returns a list of -- seven-tuples, analogous to zip. zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)] -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two lists to -- produce the list of corresponding sums. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | The zipWith3 function takes a function which combines three -- elements, as well as three lists and returns a list of their -- point-wise combination, analogous to zipWith. zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] -- | The zipWith4 function takes a function which combines four -- elements, as well as four lists and returns a list of their point-wise -- combination, analogous to zipWith. zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] -- | The zipWith5 function takes a function which combines five -- elements, as well as five lists and returns a list of their point-wise -- combination, analogous to zipWith. zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -- | The zipWith6 function takes a function which combines six -- elements, as well as six lists and returns a list of their point-wise -- combination, analogous to zipWith. zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -- | The zipWith7 function takes a function which combines seven -- elements, as well as seven lists and returns a list of their -- point-wise combination, analogous to zipWith. zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -- | unzip transforms a list of pairs into a list of first -- components and a list of second components. unzip :: [(a, b)] -> ([a], [b]) -- | The unzip3 function takes a list of triples and returns three -- lists, analogous to unzip. unzip3 :: [(a, b, c)] -> ([a], [b], [c]) -- | The unzip4 function takes a list of quadruples and returns four -- lists, analogous to unzip. unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) -- | The unzip5 function takes a list of five-tuples and returns -- five lists, analogous to unzip. unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e]) -- | The unzip6 function takes a list of six-tuples and returns six -- lists, analogous to unzip. unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) -- | The unzip7 function takes a list of seven-tuples and returns -- seven lists, analogous to unzip. unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space. words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. unlines :: [String] -> String -- | unwords is an inverse operation to words. It joins words -- with separating spaces. unwords :: [String] -> String -- | O(n^2). The nub function removes duplicate elements from -- a list. In particular, it keeps only the first occurrence of each -- element. (The name nub means `essence'.) It is a special case -- of nubBy, which allows the programmer to supply their own -- equality test. nub :: Eq a => [a] -> [a] -- | delete x removes the first occurrence of x -- from its list argument. For example, -- --
-- delete 'a' "banana" == "bnana" ---- -- It is a special case of deleteBy, which allows the programmer -- to supply their own equality test. delete :: Eq a => a -> [a] -> [a] -- | The \\ function is list difference (non-associative). In the -- result of xs \\ ys, the first occurrence of -- each element of ys in turn (if any) has been removed from -- xs. Thus -- --
-- (xs ++ ys) \\ xs == ys. ---- -- It is a special case of deleteFirstsBy, which allows the -- programmer to supply their own equality test. (\\) :: Eq a => [a] -> [a] -> [a] -- | The union function returns the list union of the two lists. For -- example, -- --
-- "dog" `union` "cow" == "dogcw" ---- -- Duplicates, and elements of the first list, are removed from the the -- second list, but if the first list contains duplicates, so will the -- result. It is a special case of unionBy, which allows the -- programmer to supply their own equality test. union :: Eq a => [a] -> [a] -> [a] -- | The intersect function takes the list intersection of two -- lists. For example, -- --
-- [1,2,3,4] `intersect` [2,4,6,8] == [2,4] ---- -- If the first list contains duplicates, so will the result. -- --
-- [1,2,2,3,4] `intersect` [6,4,4,2] == [2,2,4] ---- -- It is a special case of intersectBy, which allows the -- programmer to supply their own equality test. intersect :: Eq a => [a] -> [a] -> [a] -- | The sort function implements a stable sorting algorithm. It is -- a special case of sortBy, which allows the programmer to supply -- their own comparison function. sort :: Ord a => [a] -> [a] -- | The insert function takes an element and a list and inserts the -- element into the list at the last position where it is still less than -- or equal to the next element. In particular, if the list is sorted -- before the call, the result will also be sorted. It is a special case -- of insertBy, which allows the programmer to supply their own -- comparison function. insert :: Ord a => a -> [a] -> [a] -- | The nubBy function behaves just like nub, except it uses -- a user-supplied equality predicate instead of the overloaded == -- function. nubBy :: (a -> a -> Bool) -> [a] -> [a] -- | The deleteBy function behaves like delete, but takes a -- user-supplied equality predicate. deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a] -- | The deleteFirstsBy function takes a predicate and two lists and -- returns the first list with the first occurrence of each element of -- the second list removed. deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The unionBy function is the non-overloaded version of -- union. unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The intersectBy function is the non-overloaded version of -- intersect. intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (a -> a -> Bool) -> [a] -> [[a]] -- | The sortBy function is the non-overloaded version of -- sort. sortBy :: (a -> a -> Ordering) -> [a] -> [a] -- | The non-overloaded version of insert. insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] -- | The maximumBy function takes a comparison function and a list -- and returns the greatest element of the list by the comparison -- function. The list must be finite and non-empty. maximumBy :: (a -> a -> Ordering) -> [a] -> a -- | The minimumBy function takes a comparison function and a list -- and returns the least element of the list by the comparison function. -- The list must be finite and non-empty. minimumBy :: (a -> a -> Ordering) -> [a] -> a -- | The genericLength function is an overloaded version of -- length. In particular, instead of returning an Int, it -- returns any type which is an instance of Num. It is, however, -- less efficient than length. genericLength :: Num i => [b] -> i -- | The genericTake function is an overloaded version of -- take, which accepts any Integral value as the number of -- elements to take. genericTake :: Integral i => i -> [a] -> [a] -- | The genericDrop function is an overloaded version of -- drop, which accepts any Integral value as the number of -- elements to drop. genericDrop :: Integral i => i -> [a] -> [a] -- | The genericSplitAt function is an overloaded version of -- splitAt, which accepts any Integral value as the -- position at which to split. genericSplitAt :: Integral i => i -> [b] -> ([b], [b]) -- | The genericIndex function is an overloaded version of -- !!, which accepts any Integral value as the index. genericIndex :: Integral a => [b] -> a -> b -- | The genericReplicate function is an overloaded version of -- replicate, which accepts any Integral value as the -- number of repetitions to make. genericReplicate :: Integral i => i -> a -> [a] -- | The representations of the types TyCon and TypeRep, and the function -- mkTyCon which is used by derived instances of Typeable to construct a -- TyCon. module Data.Typeable.Internal -- | A concrete representation of a (monomorphic) type. TypeRep -- supports reasonably efficient equality. data TypeRep TypeRep :: {-# UNPACK #-} !Fingerprint -> TyCon -> [TypeRep] -> TypeRep -- | An abstract representation of a type constructor. TyCon objects -- can be built using mkTyCon. data TyCon TyCon :: {-# UNPACK #-} !Fingerprint -> String -> String -> String -> TyCon tyConHash :: TyCon -> {-# UNPACK #-} !Fingerprint tyConPackage :: TyCon -> String tyConModule :: TyCon -> String tyConName :: TyCon -> String mkTyCon :: Word# -> Word# -> String -> String -> String -> TyCon -- | Builds a TyCon object representing a type constructor. An -- implementation of Data.Typeable should ensure that the -- following holds: -- --
-- A==A' ^ B==B' ^ C==C' ==> mkTyCon A B C == mkTyCon A' B' C' --mkTyCon3 :: String -> String -> String -> TyCon -- | Applies a type constructor to a sequence of types mkTyConApp :: TyCon -> [TypeRep] -> TypeRep -- | Adds a TypeRep argument to a TypeRep. mkAppTy :: TypeRep -> TypeRep -> TypeRep -- | Observe the type constructor of a type representation typeRepTyCon :: TypeRep -> TyCon -- | For defining a Typeable instance from any Typeable1 -- instance. typeOfDefault :: (Typeable1 t, Typeable a) => t a -> TypeRep -- | For defining a Typeable1 instance from any Typeable2 -- instance. typeOf1Default :: (Typeable2 t, Typeable a) => t a b -> TypeRep -- | For defining a Typeable2 instance from any Typeable3 -- instance. typeOf2Default :: (Typeable3 t, Typeable a) => t a b c -> TypeRep -- | For defining a Typeable3 instance from any Typeable4 -- instance. typeOf3Default :: (Typeable4 t, Typeable a) => t a b c d -> TypeRep -- | For defining a Typeable4 instance from any Typeable5 -- instance. typeOf4Default :: (Typeable5 t, Typeable a) => t a b c d e -> TypeRep -- | For defining a Typeable5 instance from any Typeable6 -- instance. typeOf5Default :: (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep -- | For defining a Typeable6 instance from any Typeable7 -- instance. typeOf6Default :: (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable a typeOf :: Typeable a => a -> TypeRep -- | Variant for unary type constructors class Typeable1 t typeOf1 :: Typeable1 t => t a -> TypeRep -- | Variant for binary type constructors class Typeable2 t typeOf2 :: Typeable2 t => t a b -> TypeRep -- | Variant for 3-ary type constructors class Typeable3 t typeOf3 :: Typeable3 t => t a b c -> TypeRep -- | Variant for 4-ary type constructors class Typeable4 t typeOf4 :: Typeable4 t => t a b c d -> TypeRep -- | Variant for 5-ary type constructors class Typeable5 t typeOf5 :: Typeable5 t => t a b c d e -> TypeRep -- | Variant for 6-ary type constructors class Typeable6 t typeOf6 :: Typeable6 t => t a b c d e f -> TypeRep -- | Variant for 7-ary type constructors class Typeable7 t typeOf7 :: Typeable7 t => t a b c d e f g -> TypeRep -- | A special case of mkTyConApp, which applies the function type -- constructor to a pair of types. mkFunTy :: TypeRep -> TypeRep -> TypeRep -- | Splits a type constructor application splitTyConApp :: TypeRep -> (TyCon, [TypeRep]) -- | Applies a type to a function type. Returns: Just u if -- the first argument represents a function of type t -> u -- and the second argument represents a function of type t. -- Otherwise, returns Nothing. funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep -- | Observe the argument types of a type representation typeRepArgs :: TypeRep -> [TypeRep] showsTypeRep :: TypeRep -> ShowS -- | Observe string encoding of a type representation -- | Deprecated: renamed to tyConName; tyConModule and tyConPackage are -- also available. tyConString :: TyCon -> String listTc :: TyCon funTc :: TyCon instance [overlap ok] Typeable TypeRep instance [overlap ok] Typeable TyCon instance [overlap ok] Typeable Word64 instance [overlap ok] Typeable Word32 instance [overlap ok] Typeable Word16 instance [overlap ok] Typeable Word8 instance [overlap ok] Typeable Int64 instance [overlap ok] Typeable Int32 instance [overlap ok] Typeable Int16 instance [overlap ok] Typeable Int8 instance [overlap ok] Typeable Ordering instance [overlap ok] Typeable Integer instance [overlap ok] Typeable Word instance [overlap ok] Typeable Int instance [overlap ok] Typeable Double instance [overlap ok] Typeable Float instance [overlap ok] Typeable Char instance [overlap ok] Typeable Bool instance [overlap ok] Typeable1 IORef instance [overlap ok] Typeable1 StablePtr instance [overlap ok] Typeable1 FunPtr instance [overlap ok] Typeable1 Ptr instance [overlap ok] Typeable7 (,,,,,,) instance [overlap ok] Typeable6 (,,,,,) instance [overlap ok] Typeable5 (,,,,) instance [overlap ok] Typeable4 (,,,) instance [overlap ok] Typeable3 (,,) instance [overlap ok] Typeable2 (,) instance [overlap ok] Typeable3 STArray instance [overlap ok] Typeable2 STRef instance [overlap ok] Typeable2 ST instance [overlap ok] Typeable2 IOArray instance [overlap ok] Typeable2 Array instance [overlap ok] Typeable1 MVar instance [overlap ok] Typeable1 IO instance [overlap ok] Typeable1 Ratio instance [overlap ok] Typeable1 Maybe instance [overlap ok] Typeable1 [] instance [overlap ok] Typeable () instance [overlap ok] Typeable RealWorld instance [overlap ok] Typeable2 (->) instance [overlap ok] Show TyCon instance [overlap ok] Show TypeRep instance [overlap ok] (Typeable7 s, Typeable a) => Typeable6 (s a) instance [overlap ok] (Typeable6 s, Typeable a) => Typeable5 (s a) instance [overlap ok] (Typeable5 s, Typeable a) => Typeable4 (s a) instance [overlap ok] (Typeable4 s, Typeable a) => Typeable3 (s a) instance [overlap ok] (Typeable3 s, Typeable a) => Typeable2 (s a) instance [overlap ok] (Typeable2 s, Typeable a) => Typeable1 (s a) instance [overlap ok] (Typeable1 s, Typeable a) => Typeable (s a) instance [overlap ok] Ord TyCon instance [overlap ok] Eq TyCon instance [overlap ok] Ord TypeRep instance [overlap ok] Eq TypeRep -- | The Typeable class reifies types to some extent by associating -- type representations to types. These type representations can be -- compared, and one can in turn define a type-safe cast operation. To -- this end, an unsafe cast is guarded by a test for type -- (representation) equivalence. The module Data.Dynamic uses -- Typeable for an implementation of dynamics. The module -- Data.Data uses Typeable and type-safe cast (but not dynamics) -- to support the "Scrap your boilerplate" style of generic programming. module Data.Typeable -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable a typeOf :: Typeable a => a -> TypeRep -- | The type-safe cast operation cast :: (Typeable a, Typeable b) => a -> Maybe b -- | A flexible variation parameterised in a type constructor gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b) -- | A concrete representation of a (monomorphic) type. TypeRep -- supports reasonably efficient equality. data TypeRep showsTypeRep :: TypeRep -> ShowS -- | An abstract representation of a type constructor. TyCon objects -- can be built using mkTyCon. data TyCon -- | Observe string encoding of a type representation tyConString :: TyCon -> String tyConPackage :: TyCon -> String tyConModule :: TyCon -> String tyConName :: TyCon -> String -- | Backwards-compatible API -- | Deprecated: either derive Typeable, or use mkTyCon3 instead mkTyCon :: String -> TyCon -- | Builds a TyCon object representing a type constructor. An -- implementation of Data.Typeable should ensure that the -- following holds: -- --
-- A==A' ^ B==B' ^ C==C' ==> mkTyCon A B C == mkTyCon A' B' C' --mkTyCon3 :: String -> String -> String -> TyCon -- | Applies a type constructor to a sequence of types mkTyConApp :: TyCon -> [TypeRep] -> TypeRep -- | Adds a TypeRep argument to a TypeRep. mkAppTy :: TypeRep -> TypeRep -> TypeRep -- | A special case of mkTyConApp, which applies the function type -- constructor to a pair of types. mkFunTy :: TypeRep -> TypeRep -> TypeRep -- | Splits a type constructor application splitTyConApp :: TypeRep -> (TyCon, [TypeRep]) -- | Applies a type to a function type. Returns: Just u if -- the first argument represents a function of type t -> u -- and the second argument represents a function of type t. -- Otherwise, returns Nothing. funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep -- | Observe the type constructor of a type representation typeRepTyCon :: TypeRep -> TyCon -- | Observe the argument types of a type representation typeRepArgs :: TypeRep -> [TypeRep] -- | (DEPRECATED) Returns a unique key associated with a TypeRep. -- This function is deprecated because TypeRep itself is now an -- instance of Ord, so mappings can be made directly with -- TypeRep as the key. -- | Deprecated: TypeRep itself is now an instance of Ord typeRepKey :: TypeRep -> IO TypeRepKey data TypeRepKey -- | Variant for unary type constructors class Typeable1 t typeOf1 :: Typeable1 t => t a -> TypeRep -- | Variant for binary type constructors class Typeable2 t typeOf2 :: Typeable2 t => t a b -> TypeRep -- | Variant for 3-ary type constructors class Typeable3 t typeOf3 :: Typeable3 t => t a b c -> TypeRep -- | Variant for 4-ary type constructors class Typeable4 t typeOf4 :: Typeable4 t => t a b c d -> TypeRep -- | Variant for 5-ary type constructors class Typeable5 t typeOf5 :: Typeable5 t => t a b c d e -> TypeRep -- | Variant for 6-ary type constructors class Typeable6 t typeOf6 :: Typeable6 t => t a b c d e f -> TypeRep -- | Variant for 7-ary type constructors class Typeable7 t typeOf7 :: Typeable7 t => t a b c d e f g -> TypeRep -- | Cast for * -> * gcast1 :: (Typeable1 t, Typeable1 t') => c (t a) -> Maybe (c (t' a)) -- | Cast for * -> * -> * gcast2 :: (Typeable2 t, Typeable2 t') => c (t a b) -> Maybe (c (t' a b)) -- | For defining a Typeable instance from any Typeable1 -- instance. typeOfDefault :: (Typeable1 t, Typeable a) => t a -> TypeRep -- | For defining a Typeable1 instance from any Typeable2 -- instance. typeOf1Default :: (Typeable2 t, Typeable a) => t a b -> TypeRep -- | For defining a Typeable2 instance from any Typeable3 -- instance. typeOf2Default :: (Typeable3 t, Typeable a) => t a b c -> TypeRep -- | For defining a Typeable3 instance from any Typeable4 -- instance. typeOf3Default :: (Typeable4 t, Typeable a) => t a b c d -> TypeRep -- | For defining a Typeable4 instance from any Typeable5 -- instance. typeOf4Default :: (Typeable5 t, Typeable a) => t a b c d e -> TypeRep -- | For defining a Typeable5 instance from any Typeable6 -- instance. typeOf5Default :: (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep -- | For defining a Typeable6 instance from any Typeable7 -- instance. typeOf6Default :: (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep instance [overlap ok] Eq TypeRepKey instance [overlap ok] Ord TypeRepKey -- | The Either type, and associated operations. module Data.Either -- | The Either type represents values with two possibilities: a -- value of type Either a b is either Left -- a or Right b. -- -- The Either type is sometimes used to represent a value which is -- either correct or an error; by convention, the Left constructor -- is used to hold an error value and the Right constructor is -- used to hold a correct value (mnemonic: "right" also means "correct"). data Either a b Left :: a -> Either a b Right :: b -> Either a b -- | Case analysis for the Either type. If the value is -- Left a, apply the first function to a; if it -- is Right b, apply the second function to b. either :: (a -> c) -> (b -> c) -> Either a b -> c -- | Extracts from a list of Either all the Left elements All -- the Left elements are extracted in order. lefts :: [Either a b] -> [a] -- | Extracts from a list of Either all the Right elements -- All the Right elements are extracted in order. rights :: [Either a b] -> [b] -- | Partitions a list of Either into two lists All the Left -- elements are extracted, in order, to the first component of the -- output. Similarly the Right elements are extracted to the -- second component of the output. partitionEithers :: [Either a b] -> ([a], [b]) instance Typeable2 Either instance (Eq a, Eq b) => Eq (Either a b) instance (Ord a, Ord b) => Ord (Either a b) instance (Read a, Read b) => Read (Either a b) instance (Show a, Show b) => Show (Either a b) instance Generic (Either a b) instance Datatype D1Either instance Constructor C1_0Either instance Constructor C1_1Either -- | Converting strings to values. -- -- The Text.Read library is the canonical library to import for -- Read-class facilities. For GHC only, it offers an extended and -- much improved Read class, which constitutes a proposed -- alternative to the Haskell 98 Read. In particular, writing -- parsers is easier, and the parsers are much more efficient. module Text.Read -- | Parsing of Strings, producing values. -- -- Minimal complete definition: readsPrec (or, for GHC only, -- readPrec) -- -- Derived instances of Read make the following assumptions, which -- derived instances of Show obey: -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Read in Haskell 98 is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readsPrec d r = readParen (d > app_prec) -- (\r -> [(Leaf m,t) | -- ("Leaf",s) <- lex r, -- (m,t) <- readsPrec (app_prec+1) s]) r -- -- ++ readParen (d > up_prec) -- (\r -> [(u:^:v,w) | -- (u,s) <- readsPrec (up_prec+1) r, -- (":^:",t) <- lex s, -- (v,w) <- readsPrec (up_prec+1) t]) r -- -- where app_prec = 10 -- up_prec = 5 ---- -- Note that right-associativity of :^: is unused. -- -- The derived instance in GHC is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readPrec = parens $ (prec app_prec $ do -- Ident "Leaf" <- lexP -- m <- step readPrec -- return (Leaf m)) -- -- +++ (prec up_prec $ do -- u <- step readPrec -- Symbol ":^:" <- lexP -- v <- step readPrec -- return (u :^: v)) -- -- where app_prec = 10 -- up_prec = 5 -- -- readListPrec = readListPrecDefault --class Read a where readsPrec = readPrec_to_S readPrec readList = readPrec_to_S (list readPrec) 0 readPrec = readS_to_Prec readsPrec readListPrec = readS_to_Prec (\ _ -> readList) readsPrec :: Read a => Int -> ReadS a readList :: Read a => ReadS [a] readPrec :: Read a => ReadPrec a readListPrec :: Read a => ReadPrec [a] -- | A parser for a type a, represented as a function that takes a -- String and returns a list of possible parses as -- (a,String) pairs. -- -- Note that this kind of backtracking parser is very inefficient; -- reading a large structure may be quite slow (cf ReadP). type ReadS a = String -> [(a, String)] -- | equivalent to readsPrec with a precedence of 0. reads :: Read a => ReadS a -- | The read function reads input from a string, which must be -- completely consumed by the input process. read :: Read a => String -> a -- | readParen True p parses what p parses, -- but surrounded with parentheses. -- -- readParen False p parses what p -- parses, but optionally surrounded with parentheses. readParen :: Bool -> ReadS a -> ReadS a -- | The lex function reads a single lexeme from the input, -- discarding initial white space, and returning the characters that -- constitute the lexeme. If the input string contains only white space, -- lex returns a single successful `lexeme' consisting of the -- empty string. (Thus lex "" = [("","")].) If there is -- no legal lexeme at the beginning of the input string, lex fails -- (i.e. returns []). -- -- This lexer is not completely faithful to the Haskell lexical syntax in -- the following respects: -- --
-- toDyn (id :: Int -> Int) --toDyn :: Typeable a => a -> Dynamic -- | Converts a Dynamic object back into an ordinary Haskell value -- of the correct type. See also fromDynamic. fromDyn :: Typeable a => Dynamic -> a -> a -- | Converts a Dynamic object back into an ordinary Haskell value -- of the correct type. See also fromDyn. fromDynamic :: Typeable a => Dynamic -> Maybe a dynApply :: Dynamic -> Dynamic -> Maybe Dynamic dynApp :: Dynamic -> Dynamic -> Dynamic dynTypeRep :: Dynamic -> TypeRep instance Typeable Dynamic instance Exception Dynamic instance Show Dynamic -- | The String type and associated operations. module Data.String -- | A String is a list of characters. String constants in Haskell -- are values of type String. type String = [Char] -- | Class for string-like datastructures; used by the overloaded string -- extension (-foverloaded-strings in GHC). class IsString a fromString :: IsString a => String -> a -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space. words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. unlines :: [String] -> String -- | unwords is an inverse operation to words. It joins words -- with separating spaces. unwords :: [String] -> String instance IsString [Char] -- | This module provides typed pointers to foreign data. It is part of the -- Foreign Function Interface (FFI) and will normally be imported via the -- Foreign module. module Foreign.Ptr -- | A value of type Ptr a represents a pointer to an -- object, or an array of objects, which may be marshalled to or from -- Haskell values of type a. -- -- The type a will often be an instance of class Storable -- which provides the marshalling operations. However this is not -- essential, and you can provide your own operations to access the -- pointer. For example you might write small foreign functions to get or -- set the fields of a C struct. data Ptr a -- | The constant nullPtr contains a distinguished value of -- Ptr that is not associated with a valid memory location. nullPtr :: Ptr a -- | The castPtr function casts a pointer from one type to another. castPtr :: Ptr a -> Ptr b -- | Advances the given address by the given offset in bytes. plusPtr :: Ptr a -> Int -> Ptr b -- | Given an arbitrary address and an alignment constraint, -- alignPtr yields the next higher address that fulfills the -- alignment constraint. An alignment constraint x is fulfilled -- by any address divisible by x. This operation is idempotent. alignPtr :: Ptr a -> Int -> Ptr a -- | Computes the offset required to get from the second to the first -- argument. We have -- --
-- p2 == p1 `plusPtr` (p2 `minusPtr` p1) --minusPtr :: Ptr a -> Ptr b -> Int -- | A value of type FunPtr a is a pointer to a function -- callable from foreign code. The type a will normally be a -- foreign type, a function type with zero or more arguments where -- --
-- foreign import ccall "stdlib.h &free" -- p_free :: FunPtr (Ptr a -> IO ()) ---- -- or a pointer to a Haskell function created using a wrapper stub -- declared to produce a FunPtr of the correct type. For example: -- --
-- type Compare = Int -> Int -> Bool -- foreign import ccall "wrapper" -- mkCompare :: Compare -> IO (FunPtr Compare) ---- -- Calls to wrapper stubs like mkCompare allocate storage, which -- should be released with freeHaskellFunPtr when no longer -- required. -- -- To convert FunPtr values to corresponding Haskell functions, -- one can define a dynamic stub for the specific foreign type, -- e.g. -- --
-- type IntFunction = CInt -> IO () -- foreign import ccall "dynamic" -- mkFun :: FunPtr IntFunction -> IntFunction --data FunPtr a -- | The constant nullFunPtr contains a distinguished value of -- FunPtr that is not associated with a valid memory location. nullFunPtr :: FunPtr a -- | Casts a FunPtr to a FunPtr of a different type. castFunPtr :: FunPtr a -> FunPtr b -- | Casts a FunPtr to a Ptr. -- -- Note: this is valid only on architectures where data and -- function pointers range over the same set of addresses, and should -- only be used for bindings to external libraries whose interface -- already relies on this assumption. castFunPtrToPtr :: FunPtr a -> Ptr b -- | Casts a Ptr to a FunPtr. -- -- Note: this is valid only on architectures where data and -- function pointers range over the same set of addresses, and should -- only be used for bindings to external libraries whose interface -- already relies on this assumption. castPtrToFunPtr :: Ptr a -> FunPtr b -- | Release the storage associated with the given FunPtr, which -- must have been obtained from a wrapper stub. This should be called -- whenever the return value from a foreign import wrapper function is no -- longer required; otherwise, the storage it uses will leak. freeHaskellFunPtr :: FunPtr a -> IO () -- | A signed integral type that can be losslessly converted to and from -- Ptr. This type is also compatible with the C99 type -- intptr_t, and can be marshalled to and from that type safely. data IntPtr -- | casts a Ptr to an IntPtr ptrToIntPtr :: Ptr a -> IntPtr -- | casts an IntPtr to a Ptr intPtrToPtr :: IntPtr -> Ptr a -- | An unsigned integral type that can be losslessly converted to and from -- Ptr. This type is also compatible with the C99 type -- uintptr_t, and can be marshalled to and from that type -- safely. data WordPtr -- | casts a Ptr to a WordPtr ptrToWordPtr :: Ptr a -> WordPtr -- | casts a WordPtr to a Ptr wordPtrToPtr :: WordPtr -> Ptr a instance Typeable IntPtr instance Typeable WordPtr instance Eq WordPtr instance Ord WordPtr instance Num WordPtr instance Enum WordPtr instance Storable WordPtr instance Real WordPtr instance Bounded WordPtr instance Integral WordPtr instance Bits WordPtr instance Eq IntPtr instance Ord IntPtr instance Num IntPtr instance Enum IntPtr instance Storable IntPtr instance Real IntPtr instance Bounded IntPtr instance Integral IntPtr instance Bits IntPtr instance Show IntPtr instance Read IntPtr instance Show WordPtr instance Read WordPtr -- | Mutable references in the IO monad. module Data.IORef -- | A mutable variable in the IO monad data IORef a -- | Build a new IORef newIORef :: a -> IO (IORef a) -- | Read the value of an IORef readIORef :: IORef a -> IO a -- | Write a new value into an IORef writeIORef :: IORef a -> a -> IO () -- | Mutate the contents of an IORef modifyIORef :: IORef a -> (a -> a) -> IO () -- | Atomically modifies the contents of an IORef. -- -- This function is useful for using IORef in a safe way in a -- multithreaded program. If you only have one IORef, then using -- atomicModifyIORef to access and modify it will prevent race -- conditions. -- -- Extending the atomicity to multiple IORefs is problematic, so -- it is recommended that if you need to do anything more complicated -- then using MVar instead is a good idea. atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b -- | Make a Weak pointer to an IORef, using the second -- argument as a finalizer to run when IORef is garbage-collected mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a)) -- | A class for monoids (types with an associative binary operation that -- has an identity) with various general-purpose instances. module Data.Monoid -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following laws: -- --
mappend mempty x = x
mappend x mempty = x
mappend x (mappend y z) = mappend (mappend x y) z
mconcat = foldr mappend mempty
-- f x | x < 0 = ... -- | otherwise = ... --otherwise :: Bool -- | Equality module Data.Eq -- | The Eq class defines equality (==) and inequality -- (/=). All the basic datatypes exported by the Prelude -- are instances of Eq, and Eq may be derived for any -- datatype whose constituents are also instances of Eq. -- -- Minimal complete definition: either == or /=. class Eq a (==) :: Eq a => a -> a -> Bool (/=) :: Eq a => a -> a -> Bool -- | An implementation of extensible hash tables, as described in Per-Ake -- Larson, Dynamic Hash Tables, CACM 31(4), April 1988, pp. -- 446--457. The implementation is also derived from the one in GHC's -- runtime system (ghc/rts/Hash.{c,h}). module Data.HashTable data HashTable key val -- | Creates a new hash table. The following property should hold for the -- eq and hash functions passed to new: -- --
-- eq A B => hash A == hash B --new :: (key -> key -> Bool) -> (key -> Int32) -> IO (HashTable key val) -- | Creates a new hash table with the given minimum size. newHint :: (key -> key -> Bool) -> (key -> Int32) -> Int -> IO (HashTable key val) -- | Inserts a key/value mapping into the hash table. -- -- Note that insert doesn't remove the old entry from the table - -- the behaviour is like an association list, where lookup returns -- the most-recently-inserted mapping for a key in the table. The reason -- for this is to keep insert as efficient as possible. If you -- need to update a mapping, then we provide update. insert :: HashTable key val -> key -> val -> IO () -- | Remove an entry from the hash table. delete :: HashTable key val -> key -> IO () -- | Looks up the value of a key in the hash table. lookup :: HashTable key val -> key -> IO (Maybe val) -- | Updates an entry in the hash table, returning True if there was -- already an entry for this key, or False otherwise. After -- update there will always be exactly one entry for the given key -- in the table. -- -- insert is more efficient than update if you don't care -- about multiple entries, or you know for sure that multiple entries -- can't occur. However, update is more efficient than -- delete followed by insert. update :: HashTable key val -> key -> val -> IO Bool -- | Convert a list of key/value pairs into a hash table. Equality on keys -- is taken from the Eq instance for the key type. fromList :: Eq key => (key -> Int32) -> [(key, val)] -> IO (HashTable key val) -- | Converts a hash table to a list of key/value pairs. toList :: HashTable key val -> IO [(key, val)] -- | A sample (and useful) hash function for Int and Int32, implemented by -- extracting the uppermost 32 bits of the 64-bit result of multiplying -- by a 33-bit constant. The constant is from Knuth, derived from the -- golden ratio: -- --
-- golden = round ((sqrt 5 - 1) * 2^32) ---- -- We get good key uniqueness on small inputs (a problem with previous -- versions): (length $ group $ sort $ map hashInt [-32767..65536]) == -- 65536 + 32768 hashInt :: Int -> Int32 -- | A sample hash function for Strings. We keep multiplying by the golden -- ratio and adding. The implementation is: -- --
-- hashString = foldl' f golden -- where f m c = fromIntegral (ord c) * magic + hashInt32 m -- magic = 0xdeadbeef ---- -- Where hashInt32 works just as hashInt shown above. -- -- Knuth argues that repeated multiplication by the golden ratio will -- minimize gaps in the hash space, and thus it's a good choice for -- combining together multiple keys to form one. -- -- Here we know that individual characters c are often small, and this -- produces frequent collisions if we use ord c alone. A particular -- problem are the shorter low ASCII and ISO-8859-1 character strings. We -- pre-multiply by a magic twiddle factor to obtain a good distribution. -- In fact, given the following test: -- --
-- testp :: Int32 -> Int -- testp k = (n - ) . length . group . sort . map hs . take n $ ls -- where ls = [] : [c : l | l <- ls, c <- ['\0'..'\xff']] -- hs = foldl' f golden -- f m c = fromIntegral (ord c) * k + hashInt32 m -- n = 100000 ---- -- We discover that testp magic = 0. hashString :: String -> Int32 -- | A prime larger than the maximum hash table size prime :: Int32 -- | This function is useful for determining whether your hash function is -- working well for your data set. It returns the longest chain of -- key/value pairs in the hash table for which all the keys hash to the -- same bucket. If this chain is particularly long (say, longer than 14 -- elements or so), then it might be a good idea to try a different hash -- function. longestChain :: HashTable key val -> IO [(key, val)] instance Eq HashData instance Show HashData instance Eq Inserts -- | Orderings module Data.Ord -- | The Ord class is used for totally ordered datatypes. -- -- Instances of Ord can be derived for any user-defined datatype -- whose constituent types are in Ord. The declared order of the -- constructors in the data declaration determines the ordering in -- derived Ord instances. The Ordering datatype allows a -- single comparison to determine the precise ordering of two objects. -- -- Minimal complete definition: either compare or <=. -- Using compare can be more efficient for complex types. class Eq a => Ord a compare :: Ord a => a -> a -> Ordering (<) :: Ord a => a -> a -> Bool (>=) :: Ord a => a -> a -> Bool (>) :: Ord a => a -> a -> Bool (<=) :: Ord a => a -> a -> Bool max :: Ord a => a -> a -> a min :: Ord a => a -> a -> a data Ordering :: * LT :: Ordering EQ :: Ordering GT :: Ordering -- |
-- comparing p x y = compare (p x) (p y) ---- -- Useful combinator for use in conjunction with the xxxBy -- family of functions from Data.List, for example: -- --
-- ... sortBy (comparing fst) ... --comparing :: Ord a => (b -> a) -> b -> b -> Ordering -- | The ForeignPtr type and operations. This module is part of the -- Foreign Function Interface (FFI) and will usually be imported via the -- Foreign module. -- -- Safe API Only. module Foreign.ForeignPtr.Safe -- | 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. data ForeignPtr a -- | A finalizer is represented as a pointer to a foreign function that, at -- finalisation time, gets as an argument a plain pointer variant of the -- foreign pointer that the finalizer is associated with. type FinalizerPtr a = FunPtr (Ptr a -> IO ()) type FinalizerEnvPtr env a = FunPtr (Ptr env -> Ptr a -> IO ()) -- | Turns a plain memory reference into a foreign pointer, and associates -- a finalizer with the reference. The finalizer will be executed after -- the last reference to the foreign object is dropped. There is no -- guarantee of promptness, however the finalizer will be executed before -- the program exits. newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a) -- | Turns a plain memory reference into a foreign pointer that may be -- associated with finalizers by using addForeignPtrFinalizer. newForeignPtr_ :: Ptr a -> IO (ForeignPtr a) -- | This function adds a finalizer to the given foreign object. The -- finalizer will run before all other finalizers for the same -- object which have already been registered. addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO () -- | This variant of newForeignPtr adds a finalizer that expects an -- environment in addition to the finalized pointer. The environment that -- will be passed to the finalizer is fixed by the second argument to -- newForeignPtrEnv. newForeignPtrEnv :: FinalizerEnvPtr env a -> Ptr env -> Ptr a -> IO (ForeignPtr a) -- | Like addForeignPtrFinalizerEnv but allows the finalizer to be -- passed an additional environment parameter to be passed to the -- finalizer. The environment passed to the finalizer is fixed by the -- second argument to addForeignPtrFinalizerEnv addForeignPtrFinalizerEnv :: FinalizerEnvPtr env a -> Ptr env -> ForeignPtr a -> IO () -- | This is a way to look at the pointer living inside a foreign object. -- This function takes a function which is applied to that pointer. The -- resulting IO action is then executed. The foreign object is -- kept alive at least during the whole action, even if it is not used -- directly inside. Note that it is not safe to return the pointer from -- the action and use it after the action completes. All uses of the -- pointer should be inside the withForeignPtr bracket. The reason -- for this unsafeness is the same as for unsafeForeignPtrToPtr -- below: the finalizer may run earlier than expected, because the -- compiler can only track usage of the ForeignPtr object, not a -- Ptr object made from it. -- -- This function is normally used for marshalling data to or from the -- object pointed to by the ForeignPtr, using the operations from -- the Storable class. withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b -- | Causes the finalizers associated with a foreign pointer to be run -- immediately. finalizeForeignPtr :: ForeignPtr a -> IO () -- | This function ensures that the foreign object in question is alive at -- the given place in the sequence of IO actions. In particular -- withForeignPtr does a touchForeignPtr after it executes -- the user action. -- -- Note that this function should not be used to express dependencies -- between finalizers on ForeignPtrs. For example, if the -- finalizer for a ForeignPtr F1 calls -- touchForeignPtr on a second ForeignPtr F2, then -- the only guarantee is that the finalizer for F2 is never -- started before the finalizer for F1. They might be started -- together if for example both F1 and F2 are otherwise -- unreachable, and in that case the scheduler might end up running the -- finalizer for F2 first. -- -- In general, it is not recommended to use finalizers on separate -- objects with ordering constraints between them. To express the -- ordering robustly requires explicit synchronisation using -- MVars between the finalizers, but even then the runtime -- sometimes runs multiple finalizers sequentially in a single thread -- (for performance reasons), so synchronisation between finalizers could -- result in artificial deadlock. Another alternative is to use explicit -- reference counting. touchForeignPtr :: ForeignPtr a -> IO () -- | This function casts a ForeignPtr parameterised by one type into -- another type. castForeignPtr :: ForeignPtr a -> ForeignPtr b -- | Allocate some memory and return a ForeignPtr to it. The memory -- will be released automatically when the ForeignPtr is -- discarded. -- -- mallocForeignPtr is equivalent to -- --
-- do { p <- malloc; newForeignPtr finalizerFree p } ---- -- although it may be implemented differently internally: you may not -- assume that the memory returned by mallocForeignPtr has been -- allocated with malloc. -- -- GHC notes: mallocForeignPtr has a heavily optimised -- implementation in GHC. It uses pinned memory in the garbage collected -- heap, so the ForeignPtr does not require a finalizer to free -- the memory. Use of mallocForeignPtr and associated functions is -- strongly recommended in preference to newForeignPtr with a -- finalizer. mallocForeignPtr :: Storable a => IO (ForeignPtr a) -- | This function is similar to mallocForeignPtr, except that the -- size of the memory required is given explicitly as a number of bytes. mallocForeignPtrBytes :: Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray0, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray0 :: Storable a => Int -> IO (ForeignPtr a) -- | The ForeignPtr type and operations. This module is part of the -- Foreign Function Interface (FFI) and will usually be imported via the -- Foreign module. -- -- Unsafe API Only. module Foreign.ForeignPtr.Unsafe -- | This function extracts the pointer component of a foreign pointer. -- This is a potentially dangerous operations, as if the argument to -- unsafeForeignPtrToPtr is the last usage occurrence of the given -- foreign pointer, then its finalizer(s) will be run, which potentially -- invalidates the plain pointer just obtained. Hence, -- touchForeignPtr must be used wherever it has to be guaranteed -- that the pointer lives on - i.e., has another usage occurrence. -- -- To avoid subtle coding errors, hand written marshalling code should -- preferably use withForeignPtr rather than combinations of -- unsafeForeignPtrToPtr and touchForeignPtr. However, the -- latter routines are occasionally preferred in tool generated -- marshalling code. unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a -- | Buffers used in the IO system module GHC.IO.Buffer -- | A mutable array of bytes that can be passed to foreign functions. -- -- The buffer is represented by a record, where the record contains the -- raw buffer and the start/end points of the filled portion. The buffer -- contents itself is mutable, but the rest of the record is immutable. -- This is a slightly odd mix, but it turns out to be quite practical: by -- making all the buffer metadata immutable, we can have operations on -- buffer metadata outside of the IO monad. -- -- The live elements of the buffer are those between the -- bufL and bufR offsets. In an empty buffer, bufL -- is equal to bufR, but they might not be zero: for exmaple, the -- buffer might correspond to a memory-mapped file and in which case -- bufL will point to the next location to be written, which is -- not necessarily the beginning of the file. data Buffer e Buffer :: !RawBuffer e -> BufferState -> !Int -> !Int -> !Int -> Buffer e bufRaw :: Buffer e -> !RawBuffer e bufState :: Buffer e -> BufferState bufSize :: Buffer e -> !Int bufL :: Buffer e -> !Int bufR :: Buffer e -> !Int data BufferState ReadBuffer :: BufferState WriteBuffer :: BufferState type CharBuffer = Buffer Char type CharBufElem = Char newByteBuffer :: Int -> BufferState -> IO (Buffer Word8) newCharBuffer :: Int -> BufferState -> IO CharBuffer newBuffer :: Int -> Int -> BufferState -> IO (Buffer e) emptyBuffer :: RawBuffer e -> Int -> BufferState -> Buffer e bufferRemove :: Int -> Buffer e -> Buffer e bufferAdd :: Int -> Buffer e -> Buffer e -- | slides the contents of the buffer to the beginning slideContents :: Buffer Word8 -> IO (Buffer Word8) bufferAdjustL :: Int -> Buffer e -> Buffer e isEmptyBuffer :: Buffer e -> Bool isFullBuffer :: Buffer e -> Bool isFullCharBuffer :: Buffer e -> Bool isWriteBuffer :: Buffer e -> Bool bufferElems :: Buffer e -> Int bufferAvailable :: Buffer e -> Int summaryBuffer :: Buffer a -> String withBuffer :: Buffer e -> (Ptr e -> IO a) -> IO a withRawBuffer :: RawBuffer e -> (Ptr e -> IO a) -> IO a checkBuffer :: Buffer a -> IO () type RawBuffer e = ForeignPtr e readWord8Buf :: RawBuffer Word8 -> Int -> IO Word8 writeWord8Buf :: RawBuffer Word8 -> Int -> Word8 -> IO () type RawCharBuffer = RawBuffer CharBufElem peekCharBuf :: RawCharBuffer -> Int -> IO Char readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int) writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int) writeCharBufPtr :: Ptr CharBufElem -> Int -> Char -> IO Int charSize :: Int instance Eq BufferState -- | Types for text encoding/decoding module GHC.IO.Encoding.Types data BufferCodec from to state BufferCodec :: (Buffer from -> Buffer to -> IO (CodingProgress, Buffer from, Buffer to)) -> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to)) -> IO () -> IO state -> (state -> IO ()) -> BufferCodec from to state -- | The encode function translates elements of the buffer -- from to the buffer to. It should translate as many -- elements as possible given the sizes of the buffers, including -- translating zero elements if there is either not enough room in -- to, or from does not contain a complete multibyte -- sequence. -- -- The fact that as many elements as possible are translated is used by -- the IO library in order to report translation errors at the point they -- actually occur, rather than when the buffer is translated. -- -- To allow us to use iconv as a BufferCode efficiently, character -- buffers are defined to contain lone surrogates instead of those -- private use characters that are used for roundtripping. Thus, Chars -- poked and peeked from a character buffer must undergo -- surrogatifyRoundtripCharacter and desurrogatifyRoundtripCharacter -- respectively. -- -- For more information on this, see Note [Roundtripping] in -- GHC.IO.Encoding.Failure. encode :: BufferCodec from to state -> Buffer from -> Buffer to -> IO (CodingProgress, Buffer from, Buffer to) -- | The recover function is used to continue decoding in the -- presence of invalid or unrepresentable sequences. This includes both -- those detected by encode returning InvalidSequence -- and those that occur because the input byte sequence appears to be -- truncated. -- -- Progress will usually be made by skipping the first element of the -- from buffer. This function should only be called if you are -- certain that you wish to do this skipping and if the to -- buffer has at least one element of free space. Because this function -- deals with decoding failure, it assumes that the from buffer has at -- least one element. -- -- recover may raise an exception rather than skipping anything. -- -- Currently, some implementations of recover may mutate the -- input buffer. In particular, this feature is used to implement -- transliteration. recover :: BufferCodec from to state -> Buffer from -> Buffer to -> IO (Buffer from, Buffer to) -- | Resources associated with the encoding may now be released. The -- encode function may not be called again after calling -- close. close :: BufferCodec from to state -> IO () -- | Return the current state of the codec. -- -- Many codecs are not stateful, and in these case the state can be -- represented as '()'. Other codecs maintain a state. For example, -- UTF-16 recognises a BOM (byte-order-mark) character at the beginning -- of the input, and remembers thereafter whether to use big-endian or -- little-endian mode. In this case, the state of the codec would include -- two pieces of information: whether we are at the beginning of the -- stream (the BOM only occurs at the beginning), and if not, whether to -- use the big or little-endian encoding. getState :: BufferCodec from to state -> IO state setState :: BufferCodec from to state -> state -> IO () -- | A TextEncoding is a specification of a conversion scheme -- between sequences of bytes and sequences of Unicode characters. -- -- For example, UTF-8 is an encoding of Unicode characters into a -- sequence of bytes. The TextEncoding for UTF-8 is utf8. data TextEncoding TextEncoding :: String -> IO (TextDecoder dstate) -> IO (TextEncoder estate) -> TextEncoding -- | a string that can be passed to mkTextEncoding to create an -- equivalent TextEncoding. textEncodingName :: TextEncoding -> String -- | Creates a means of decoding bytes into characters: the result must not -- be shared between several byte sequences or simultaneously across -- threads mkTextDecoder :: TextEncoding -> IO (TextDecoder dstate) -- | Creates a means of encode characters into bytes: the result must not -- be shared between several character sequences or simultaneously across -- threads mkTextEncoder :: TextEncoding -> IO (TextEncoder estate) type TextEncoder state = BufferCodec CharBufElem Word8 state type TextDecoder state = BufferCodec Word8 CharBufElem state type EncodeBuffer = Buffer Char -> Buffer Word8 -> IO (CodingProgress, Buffer Char, Buffer Word8) type DecodeBuffer = Buffer Word8 -> Buffer Char -> IO (CodingProgress, Buffer Word8, Buffer Char) data CodingProgress -- | Stopped because the input contains insufficient available elements, or -- all of the input sequence has been sucessfully translated. InputUnderflow :: CodingProgress -- | Stopped because the output contains insufficient free elements OutputUnderflow :: CodingProgress -- | Stopped because there are sufficient free elements in the output to -- output at least one encoded ASCII character, but the input contains an -- invalid or unrepresentable sequence InvalidSequence :: CodingProgress instance Eq CodingProgress instance Show CodingProgress instance Show TextEncoding -- | Class of buffered IO devices module GHC.IO.BufferedIO -- | The purpose of BufferedIO is to provide a common interface for -- I/O devices that can read and write data through a buffer. Devices -- that implement BufferedIO include ordinary files, memory-mapped -- files, and bytestrings. The underlying device implementing a -- Handle must provide BufferedIO. class BufferedIO dev where emptyWriteBuffer _dev buf = return (buf {bufL = 0, bufR = 0, bufState = WriteBuffer}) newBuffer :: BufferedIO dev => dev -> BufferState -> IO (Buffer Word8) fillReadBuffer :: BufferedIO dev => dev -> Buffer Word8 -> IO (Int, Buffer Word8) fillReadBuffer0 :: BufferedIO dev => dev -> Buffer Word8 -> IO (Maybe Int, Buffer Word8) emptyWriteBuffer :: BufferedIO dev => dev -> Buffer Word8 -> IO (Buffer Word8) flushWriteBuffer :: BufferedIO dev => dev -> Buffer Word8 -> IO (Buffer Word8) flushWriteBuffer0 :: BufferedIO dev => dev -> Buffer Word8 -> IO (Int, Buffer Word8) readBuf :: RawIO dev => dev -> Buffer Word8 -> IO (Int, Buffer Word8) readBufNonBlocking :: RawIO dev => dev -> Buffer Word8 -> IO (Maybe Int, Buffer Word8) writeBuf :: RawIO dev => dev -> Buffer Word8 -> IO (Buffer Word8) writeBufNonBlocking :: RawIO dev => dev -> Buffer Word8 -> IO (Int, Buffer Word8) -- | The module Foreign.Marshal.Alloc provides operations to -- allocate and deallocate blocks of raw memory (i.e., unstructured -- chunks of memory outside of the area maintained by the Haskell storage -- manager). These memory blocks are commonly used to pass compound data -- structures to foreign functions or to provide space in which compound -- result values are obtained from foreign functions. -- -- If any of the allocation functions fails, an exception is thrown. In -- some cases, memory exhaustion may mean the process is terminated. If -- free or reallocBytes is applied to a memory area that -- has been allocated with alloca or allocaBytes, the -- behaviour is undefined. Any further access to memory areas allocated -- with alloca or allocaBytes, after the computation that -- was passed to the allocation function has terminated, leads to -- undefined behaviour. Any further access to the memory area referenced -- by a pointer passed to realloc, reallocBytes, or -- free entails undefined behaviour. -- -- All storage allocated by functions that allocate based on a size in -- bytes must be sufficiently aligned for any of the basic foreign -- types that fits into the newly allocated storage. All storage -- allocated by functions that allocate based on a specific type must be -- sufficiently aligned for that type. Array allocation routines need to -- obey the same alignment constraints for each array element. module Foreign.Marshal.Alloc -- | alloca f executes the computation f, passing -- as argument a pointer to a temporarily allocated block of memory -- sufficient to hold values of type a. -- -- The memory is freed when f terminates (either normally or via -- an exception), so the pointer passed to f must not be -- used after this. alloca :: Storable a => (Ptr a -> IO b) -> IO b -- | allocaBytes n f executes the computation f, -- passing as argument a pointer to a temporarily allocated block of -- memory of n bytes. The block of memory is sufficiently -- aligned for any of the basic foreign types that fits into a memory -- block of the allocated size. -- -- The memory is freed when f terminates (either normally or via -- an exception), so the pointer passed to f must not be -- used after this. allocaBytes :: Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b -- | Allocate a block of memory that is sufficient to hold values of type -- a. The size of the area allocated is determined by the -- sizeOf method from the instance of Storable for the -- appropriate type. -- -- The memory may be deallocated using free or -- finalizerFree when no longer required. malloc :: Storable a => IO (Ptr a) -- | Allocate a block of memory of the given number of bytes. The block of -- memory is sufficiently aligned for any of the basic foreign types that -- fits into a memory block of the allocated size. -- -- The memory may be deallocated using free or -- finalizerFree when no longer required. mallocBytes :: Int -> IO (Ptr a) -- | Resize a memory area that was allocated with malloc or -- mallocBytes to the size needed to store values of type -- b. The returned pointer may refer to an entirely different -- memory area, but will be suitably aligned to hold values of type -- b. The contents of the referenced memory area will be the -- same as of the original pointer up to the minimum of the original size -- and the size of values of type b. -- -- If the argument to realloc is nullPtr, realloc -- behaves like malloc. realloc :: Storable b => Ptr a -> IO (Ptr b) -- | Resize a memory area that was allocated with malloc or -- mallocBytes to the given size. The returned pointer may refer -- to an entirely different memory area, but will be sufficiently aligned -- for any of the basic foreign types that fits into a memory block of -- the given size. The contents of the referenced memory area will be the -- same as of the original pointer up to the minimum of the original size -- and the given size. -- -- If the pointer argument to reallocBytes is nullPtr, -- reallocBytes behaves like malloc. If the requested size -- is 0, reallocBytes behaves like free. reallocBytes :: Ptr a -> Int -> IO (Ptr a) -- | Free a block of memory that was allocated with malloc, -- mallocBytes, realloc, reallocBytes, new or -- any of the newX functions in -- Foreign.Marshal.Array or Foreign.C.String. free :: Ptr a -> IO () -- | A pointer to a foreign function equivalent to free, which may -- be used as a finalizer (cf ForeignPtr) for storage allocated -- with malloc, mallocBytes, realloc or -- reallocBytes. finalizerFree :: FinalizerPtr a -- | Types for specifying how text encoding/decoding fails module GHC.IO.Encoding.Failure -- | The CodingFailureMode is used to construct -- TextEncodings, and specifies how they handle illegal -- sequences. data CodingFailureMode -- | Throw an error when an illegal sequence is encountered ErrorOnCodingFailure :: CodingFailureMode -- | Attempt to ignore and recover if an illegal sequence is encountered IgnoreCodingFailure :: CodingFailureMode -- | Replace with the closest visual match upon an illegal sequence TransliterateCodingFailure :: CodingFailureMode -- | Use the private-use escape mechanism to attempt to allow illegal -- sequences to be roundtripped. RoundtripFailure :: CodingFailureMode codingFailureModeSuffix :: CodingFailureMode -> String -- | Some characters are actually surrogate codepoints defined for -- use in UTF-16. We need to signal an invalid character if we detect -- them when encoding a sequence of Chars into Word8s -- because they won't give valid Unicode. -- -- We may also need to signal an invalid character if we detect them when -- encoding a sequence of Chars into Word8s because the -- RoundtripFailure mode creates these to round-trip bytes through -- our internal UTF-16 encoding. isSurrogate :: Char -> Bool recoverDecode :: CodingFailureMode -> Buffer Word8 -> Buffer Char -> IO (Buffer Word8, Buffer Char) recoverEncode :: CodingFailureMode -> Buffer Char -> Buffer Word8 -> IO (Buffer Char, Buffer Word8) instance Show CodingFailureMode -- | UTF-32 Codecs for the IO library -- -- Portions Copyright : (c) Tom Harper 2008-2009, (c) Bryan O'Sullivan -- 2009, (c) Duncan Coutts 2009 module GHC.IO.Encoding.Latin1 latin1 :: TextEncoding mkLatin1 :: CodingFailureMode -> TextEncoding latin1_checked :: TextEncoding mkLatin1_checked :: CodingFailureMode -> TextEncoding latin1_decode :: DecodeBuffer latin1_encode :: EncodeBuffer latin1_checked_encode :: EncodeBuffer -- | UTF-8 Codec for the IO library -- -- Portions Copyright : (c) Tom Harper 2008-2009, (c) Bryan O'Sullivan -- 2009, (c) Duncan Coutts 2009 module GHC.IO.Encoding.UTF8 utf8 :: TextEncoding mkUTF8 :: CodingFailureMode -> TextEncoding utf8_bom :: TextEncoding mkUTF8_bom :: CodingFailureMode -> TextEncoding -- | UTF-16 Codecs for the IO library -- -- Portions Copyright : (c) Tom Harper 2008-2009, (c) Bryan O'Sullivan -- 2009, (c) Duncan Coutts 2009 module GHC.IO.Encoding.UTF16 utf16 :: TextEncoding mkUTF16 :: CodingFailureMode -> TextEncoding utf16_decode :: IORef (Maybe DecodeBuffer) -> DecodeBuffer utf16_encode :: IORef Bool -> EncodeBuffer utf16be :: TextEncoding mkUTF16be :: CodingFailureMode -> TextEncoding utf16be_decode :: DecodeBuffer utf16be_encode :: EncodeBuffer utf16le :: TextEncoding mkUTF16le :: CodingFailureMode -> TextEncoding utf16le_decode :: DecodeBuffer utf16le_encode :: EncodeBuffer -- | UTF-32 Codecs for the IO library -- -- Portions Copyright : (c) Tom Harper 2008-2009, (c) Bryan O'Sullivan -- 2009, (c) Duncan Coutts 2009 module GHC.IO.Encoding.UTF32 utf32 :: TextEncoding mkUTF32 :: CodingFailureMode -> TextEncoding utf32_decode :: IORef (Maybe DecodeBuffer) -> DecodeBuffer utf32_encode :: IORef Bool -> EncodeBuffer utf32be :: TextEncoding mkUTF32be :: CodingFailureMode -> TextEncoding utf32be_decode :: DecodeBuffer utf32be_encode :: EncodeBuffer utf32le :: TextEncoding mkUTF32le :: CodingFailureMode -> TextEncoding utf32le_decode :: DecodeBuffer utf32le_encode :: EncodeBuffer -- | Routines for testing return values and raising a userError -- exception in case of values indicating an error state. module Foreign.Marshal.Error -- | Execute an IO action, throwing a userError if the -- predicate yields True when applied to the result returned by -- the IO action. If no exception is raised, return the result of -- the computation. throwIf :: (a -> Bool) -> (a -> String) -> IO a -> IO a -- | Like throwIf, but discarding the result throwIf_ :: (a -> Bool) -> (a -> String) -> IO a -> IO () -- | Guards against negative result values throwIfNeg :: (Ord a, Num a) => (a -> String) -> IO a -> IO a -- | Like throwIfNeg, but discarding the result throwIfNeg_ :: (Ord a, Num a) => (a -> String) -> IO a -> IO () -- | Guards against null pointers throwIfNull :: String -> IO (Ptr a) -> IO (Ptr a) -- | Discard the return value of an IO action void :: IO a -> IO () -- | Utilities for primitive marshaling module Foreign.Marshal.Utils -- | with val f executes the computation f, -- passing as argument a pointer to a temporarily allocated block of -- memory into which val has been marshalled (the combination of -- alloca and poke). -- -- The memory is freed when f terminates (either normally or via -- an exception), so the pointer passed to f must not be -- used after this. with :: Storable a => a -> (Ptr a -> IO b) -> IO b -- | Allocate a block of memory and marshal a value into it (the -- combination of malloc and poke). The size of the area -- allocated is determined by the sizeOf method from the instance -- of Storable for the appropriate type. -- -- The memory may be deallocated using free or -- finalizerFree when no longer required. new :: Storable a => a -> IO (Ptr a) -- | Convert a Haskell Bool to its numeric representation fromBool :: Num a => Bool -> a -- | Convert a Boolean in numeric representation to a Haskell value toBool :: (Eq a, Num a) => a -> Bool -- | Allocate storage and marshal a storable value wrapped into a -- Maybe -- -- maybeNew :: (a -> IO (Ptr b)) -> (Maybe a -> IO (Ptr b)) -- | Converts a withXXX combinator into one marshalling a value -- wrapped into a Maybe, using nullPtr to represent -- Nothing. maybeWith :: (a -> (Ptr b -> IO c) -> IO c) -> (Maybe a -> (Ptr b -> IO c) -> IO c) -- | Convert a peek combinator into a one returning Nothing if -- applied to a nullPtr maybePeek :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b) -- | Replicates a withXXX combinator over a list of objects, -- yielding a list of marshalled objects withMany :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res -- | Copies the given number of bytes from the second area (source) into -- the first (destination); the copied areas may not overlap copyBytes :: Ptr a -> Ptr a -> Int -> IO () -- | Copies the given number of bytes from the second area (source) into -- the first (destination); the copied areas may overlap moveBytes :: Ptr a -> Ptr a -> Int -> IO () -- | Marshalling support: routines allocating, storing, and retrieving -- Haskell lists that are represented as arrays in the foreign language module Foreign.Marshal.Array -- | Allocate storage for the given number of elements of a storable type -- (like malloc, but for multiple elements). mallocArray :: Storable a => Int -> IO (Ptr a) -- | Like mallocArray, but add an extra position to hold a special -- termination element. mallocArray0 :: Storable a => Int -> IO (Ptr a) -- | Temporarily allocate space for the given number of elements (like -- alloca, but for multiple elements). allocaArray :: Storable a => Int -> (Ptr a -> IO b) -> IO b -- | Like allocaArray, but add an extra position to hold a special -- termination element. allocaArray0 :: Storable a => Int -> (Ptr a -> IO b) -> IO b -- | Adjust the size of an array reallocArray :: Storable a => Ptr a -> Int -> IO (Ptr a) -- | Adjust the size of an array including an extra position for the end -- marker. reallocArray0 :: Storable a => Ptr a -> Int -> IO (Ptr a) -- | Convert an array of given length into a Haskell list. The -- implementation is tail-recursive and so uses constant stack space. peekArray :: Storable a => Int -> Ptr a -> IO [a] -- | Convert an array terminated by the given end marker into a Haskell -- list peekArray0 :: (Storable a, Eq a) => a -> Ptr a -> IO [a] -- | Write the list elements consecutive into memory pokeArray :: Storable a => Ptr a -> [a] -> IO () -- | Write the list elements consecutive into memory and terminate them -- with the given marker element pokeArray0 :: Storable a => a -> Ptr a -> [a] -> IO () -- | Write a list of storable elements into a newly allocated, consecutive -- sequence of storable values (like new, but for multiple -- elements). newArray :: Storable a => [a] -> IO (Ptr a) -- | Write a list of storable elements into a newly allocated, consecutive -- sequence of storable values, where the end is fixed by the given end -- marker newArray0 :: Storable a => a -> [a] -> IO (Ptr a) -- | Temporarily store a list of storable values in memory (like -- with, but for multiple elements). withArray :: Storable a => [a] -> (Ptr a -> IO b) -> IO b -- | Like withArray, but a terminator indicates where the array ends withArray0 :: Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b -- | Like withArray, but the action gets the number of values as an -- additional parameter withArrayLen :: Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b -- | Like withArrayLen, but a terminator indicates where the array -- ends withArrayLen0 :: Storable a => a -> [a] -> (Int -> Ptr a -> IO b) -> IO b -- | Copy the given number of elements from the second array (source) into -- the first array (destination); the copied areas may not overlap copyArray :: Storable a => Ptr a -> Ptr a -> Int -> IO () -- | Copy the given number of elements from the second array (source) into -- the first array (destination); the copied areas may overlap moveArray :: Storable a => Ptr a -> Ptr a -> Int -> IO () -- | Return the number of elements in an array, excluding the terminator lengthArray0 :: (Storable a, Eq a) => a -> Ptr a -> IO Int -- | Advance a pointer into an array by the given number of elements advancePtr :: Storable a => Ptr a -> Int -> Ptr a -- | Foreign marshalling support for CStrings with configurable encodings module GHC.Foreign -- | Marshal a NUL terminated C string into a Haskell string. peekCString :: TextEncoding -> CString -> IO String -- | Marshal a C string with explicit length into a Haskell string. peekCStringLen :: TextEncoding -> CStringLen -> IO String -- | Marshal a Haskell string into a NUL terminated C string. -- --
-- do { p <- malloc; newForeignPtr finalizerFree p } ---- -- although it may be implemented differently internally: you may not -- assume that the memory returned by mallocForeignPtr has been -- allocated with malloc. -- -- GHC notes: mallocForeignPtr has a heavily optimised -- implementation in GHC. It uses pinned memory in the garbage collected -- heap, so the ForeignPtr does not require a finalizer to free -- the memory. Use of mallocForeignPtr and associated functions is -- strongly recommended in preference to newForeignPtr with a -- finalizer. mallocForeignPtr :: Storable a => IO (ForeignPtr a) -- | This function is similar to mallocForeignPtr, except that the -- size of the memory required is given explicitly as a number of bytes. mallocForeignPtrBytes :: Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray0, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray0 :: Storable a => Int -> IO (ForeignPtr a) -- | Deprecated: Use Foreign.ForeignPtr.Unsafe.unsafeForeignPtrToPtr -- instead; This function will be removed in the next release unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a -- | Deprecated: Use System.IO.Unsafe.unsafePerformIO instead; This -- function will be removed in the next release unsafePerformIO :: IO a -> a -- | Basic concurrency stuff. module GHC.Conc.Sync -- | A ThreadId is an abstract type representing a handle to a -- thread. ThreadId is an instance of Eq, Ord and -- Show, where the Ord instance implements an arbitrary -- total ordering over ThreadIds. The Show instance lets -- you convert an arbitrary-valued ThreadId to string form; -- showing a ThreadId value is occasionally useful when debugging -- or diagnosing the behaviour of a concurrent program. -- -- Note: in GHC, if you have a ThreadId, you essentially -- have a pointer to the thread itself. This means the thread itself -- can't be garbage collected until you drop the ThreadId. This -- misfeature will hopefully be corrected at a later date. -- -- Note: Hugs does not provide any operations on other threads; it -- defines ThreadId as a synonym for (). data ThreadId ThreadId :: ThreadId# -> ThreadId -- | Sparks off 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 thread; if you want to use a -- foreign library that uses thread-local storage, use forkOS -- instead. -- -- GHC note: 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. forkIO :: IO () -> IO ThreadId -- | This function is deprecated; use forkIOWIthUnmask instead -- | Deprecated: use forkIOWithUnmask instead forkIOUnmasked :: IO () -> IO ThreadId -- | 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. forkIOWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | Like forkIO, but lets you specify on which processor the thread -- should run. Unlike a forkIO thread, a thread created by -- forkOn will stay on the same processor for its entire lifetime -- (forkIO threads can migrate between processors 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 perforamnce in some cases - -- experimentation is recommended). forkOn :: Int -> IO () -> IO ThreadId -- | This function is deprecated; use forkOn instead -- | Deprecated: renamed to forkOn forkOnIO :: Int -> IO () -> IO ThreadId -- | This function is deprecated; use forkOnWIthUnmask instead -- | Deprecated: use forkOnWithUnmask instead forkOnIOUnmasked :: Int -> IO () -> IO ThreadId -- | Like forkIOWithUnmask, but the child thread is pinned to the -- given CPU, as with forkOn. forkOnWithUnmask :: Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | the value passed to the +RTS -N flag. This is the number of -- Haskell threads that can run truly simultaneously at any given time, -- and is typically set to the number of physical processor cores on the -- machine. -- -- Strictly speaking it is better to use getNumCapabilities, -- because the number of capabilities might vary at runtime. numCapabilities :: Int -- | Returns the number of Haskell threads that can run truly -- simultaneously (on separate physical processors) at any given time. -- The number passed to forkOn is interpreted modulo this value. -- -- An implementation in which Haskell threads are mapped directly to OS -- threads might return the number of physical processor cores in the -- machine, and forkOn would be implemented using the OS's -- affinity facilities. An implementation that schedules Haskell threads -- onto a smaller number of OS threads (like GHC) would return the number -- of such OS threads that can be running simultaneously. -- -- GHC notes: this returns the number passed as the argument to the -- +RTS -N flag. In current implementations, the value is fixed -- when the program starts and never changes, but it is possible that in -- the future the number of capabilities might vary at runtime. getNumCapabilities :: IO Int -- | Set the number of Haskell threads that can run truly simultaneously -- (on separate physical processors) at any given time. -- -- GHC notes: in the current implementation, the value may only be -- increased, not decreased, by calling setNumCapabilities. -- The initial value is given by the +RTS -N flag, and the -- current value may be obtained using getNumCapabilities. setNumCapabilities :: Int -> IO () getNumProcessors :: IO Int -- | Returns the number of sparks currently in the local spark pool numSparks :: IO Int childHandler :: SomeException -> IO () -- | Returns the ThreadId of the calling thread (GHC only). myThreadId :: IO ThreadId -- | killThread raises the ThreadKilled exception in the -- given thread (GHC only). -- --
-- killThread tid = throwTo tid ThreadKilled --killThread :: ThreadId -> IO () -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. This is a useful property to -- know when dealing with race conditions: eg. if there are two threads -- that can kill each other, it is guaranteed that only one of the -- threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () par :: a -> b -> b pseq :: a -> b -> b -- | Internal function used by the RTS to run sparks. runSparks :: IO () -- | The yield action allows (forces, in a co-operative multitasking -- implementation) a context-switch to any other currently runnable -- threads (if any), and is occasionally useful when implementing -- concurrency abstractions. yield :: IO () -- | labelThread stores a string as identifier for this thread if -- you built a RTS with debugging support. This identifier will be used -- in the debugging output to make distinction of different threads -- easier (otherwise you only have the thread state object's address in -- the heap). -- -- Other applications like the graphical Concurrent Haskell Debugger -- (http://www.informatik.uni-kiel.de/~fhu/chd/) may choose to -- overload labelThread for their purposes as well. labelThread :: ThreadId -> String -> IO () -- | The current status of a thread data ThreadStatus -- | the thread is currently runnable or running ThreadRunning :: ThreadStatus -- | the thread has finished ThreadFinished :: ThreadStatus -- | the thread is blocked on some resource ThreadBlocked :: BlockReason -> ThreadStatus -- | the thread received an uncaught exception ThreadDied :: ThreadStatus data BlockReason -- | blocked on on MVar BlockedOnMVar :: BlockReason -- | blocked on a computation in progress by another thread BlockedOnBlackHole :: BlockReason -- | blocked in throwTo BlockedOnException :: BlockReason -- | blocked in retry in an STM transaction BlockedOnSTM :: BlockReason -- | currently in a foreign call BlockedOnForeignCall :: BlockReason -- | blocked on some other resource. Without -threaded, I/O and -- threadDelay show up as BlockedOnOther, with -- -threaded they show up as BlockedOnMVar. BlockedOnOther :: BlockReason threadStatus :: ThreadId -> IO ThreadStatus -- | returns the number of the capability on which the thread is currently -- running, and a boolean indicating whether the thread is locked to that -- capability or not. A thread is locked to a capability if it was -- created with forkOn. threadCapability :: ThreadId -> IO (Int, Bool) -- | A monad supporting atomic memory transactions. newtype STM a STM :: (State# RealWorld -> (# State# RealWorld, a #)) -> STM a -- | Perform a series of STM actions atomically. -- -- You cannot use atomically inside an unsafePerformIO or -- unsafeInterleaveIO. Any attempt to do so will result in a -- runtime error. (Reason: allowing this would effectively allow a -- transaction inside a transaction, depending on exactly when the thunk -- is evaluated.) -- -- However, see newTVarIO, which can be called inside -- unsafePerformIO, and which allows top-level TVars to be -- allocated. atomically :: STM a -> IO a -- | Retry execution of the current memory transaction because it has seen -- values in TVars which mean that it should not continue (e.g. the TVars -- represent a shared buffer that is now empty). The implementation may -- block the thread until one of the TVars that it has read from has been -- udpated. (GHC only) retry :: STM a -- | Compose two alternative STM actions (GHC only). If the first action -- completes without retrying then it forms the result of the orElse. -- Otherwise, if the first action retries, then the second action is -- tried in its place. If both actions retry then the orElse as a whole -- retries. orElse :: STM a -> STM a -> STM a -- | A variant of throw that can only be used within the STM -- monad. -- -- Throwing an exception in STM aborts the transaction and -- propagates the exception. -- -- Although throwSTM has a type that is an instance of the type of -- throw, the two functions are subtly different: -- --
-- throw e `seq` x ===> throw e -- throwSTM e `seq` x ===> x ---- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwSTM will only cause -- an exception to be raised when it is used within the STM monad. -- The throwSTM variant should be used in preference to -- throw to raise an exception within the STM monad because -- it guarantees ordering with respect to other STM operations, -- whereas throw does not. throwSTM :: Exception e => e -> STM a -- | Exception handling within STM actions. catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a -- | alwaysSucceeds adds a new invariant that must be true when passed to -- alwaysSucceeds, at the end of the current transaction, and at the end -- of every subsequent transaction. If it fails at any of those points -- then the transaction violating it is aborted and the exception raised -- by the invariant is propagated. alwaysSucceeds :: STM a -> STM () -- | always is a variant of alwaysSucceeds in which the invariant is -- expressed as an STM Bool action that must return True. Returning False -- or raising an exception are both treated as invariant failures. always :: STM Bool -> STM () -- | Shared memory locations that support atomic memory transactions. data TVar a TVar :: (TVar# RealWorld a) -> TVar a -- | Create a new TVar holding a value supplied newTVar :: a -> STM (TVar a) -- | IO version of newTVar. This is useful for creating -- top-level TVars using unsafePerformIO, because using -- atomically inside unsafePerformIO isn't possible. newTVarIO :: a -> IO (TVar a) -- | Return the current value stored in a TVar readTVar :: TVar a -> STM a -- | Return the current value stored in a TVar. This is equivalent to -- --
-- readTVarIO = atomically . readTVar ---- -- but works much faster, because it doesn't perform a complete -- transaction, it just reads the current value of the TVar. readTVarIO :: TVar a -> IO a -- | Write the supplied value into a TVar writeTVar :: TVar a -> a -> STM () -- | Unsafely performs IO in the STM monad. Beware: this is a highly -- dangerous thing to do. -- --
-- data MyException = ThisException | ThatException -- deriving (Show, Typeable) -- -- instance Exception MyException ---- -- The default method definitions in the Exception class do what -- we need in this case. You can now throw and catch -- ThisException and ThatException as exceptions: -- --
-- *Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) -- Caught ThisException ---- -- In more complicated examples, you may wish to define a whole hierarchy -- of exceptions: -- --
-- --------------------------------------------------------------------- -- -- Make the root exception type for all the exceptions in a compiler -- -- data SomeCompilerException = forall e . Exception e => SomeCompilerException e -- deriving Typeable -- -- instance Show SomeCompilerException where -- show (SomeCompilerException e) = show e -- -- instance Exception SomeCompilerException -- -- compilerExceptionToException :: Exception e => e -> SomeException -- compilerExceptionToException = toException . SomeCompilerException -- -- compilerExceptionFromException :: Exception e => SomeException -> Maybe e -- compilerExceptionFromException x = do -- SomeCompilerException a <- fromException x -- cast a -- -- --------------------------------------------------------------------- -- -- Make a subhierarchy for exceptions in the frontend of the compiler -- -- data SomeFrontendException = forall e . Exception e => SomeFrontendException e -- deriving Typeable -- -- instance Show SomeFrontendException where -- show (SomeFrontendException e) = show e -- -- instance Exception SomeFrontendException where -- toException = compilerExceptionToException -- fromException = compilerExceptionFromException -- -- frontendExceptionToException :: Exception e => e -> SomeException -- frontendExceptionToException = toException . SomeFrontendException -- -- frontendExceptionFromException :: Exception e => SomeException -> Maybe e -- frontendExceptionFromException x = do -- SomeFrontendException a <- fromException x -- cast a -- -- --------------------------------------------------------------------- -- -- Make an exception type for a particular frontend compiler exception -- -- data MismatchedParentheses = MismatchedParentheses -- deriving (Typeable, Show) -- -- instance Exception MismatchedParentheses where -- toException = frontendExceptionToException -- fromException = frontendExceptionFromException ---- -- We can now catch a MismatchedParentheses exception as -- MismatchedParentheses, SomeFrontendException or -- SomeCompilerException, but not other types, e.g. -- IOException: -- --
-- *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) -- Caught MismatchedParentheses -- *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) -- Caught MismatchedParentheses -- *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) -- Caught MismatchedParentheses -- *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException)) -- *** Exception: MismatchedParentheses --class (Typeable e, Show e) => Exception e where toException = SomeException fromException (SomeException e) = cast e toException :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Exceptions that occur in the IO monad. An -- IOException records a more specific error type, a descriptive -- string and maybe the handle that was used when the error was flagged. data IOException -- | Arithmetic exceptions. data ArithException Overflow :: ArithException Underflow :: ArithException LossOfPrecision :: ArithException DivideByZero :: ArithException Denormal :: ArithException -- | Exceptions generated by array operations data ArrayException -- | An attempt was made to index an array outside its declared bounds. IndexOutOfBounds :: String -> ArrayException -- | An attempt was made to evaluate an element of an array that had not -- been initialized. UndefinedElement :: String -> ArrayException -- | assert was applied to False. data AssertionFailed AssertionFailed :: String -> AssertionFailed -- | Asynchronous exceptions. data AsyncException -- | The current thread's stack exceeded its limit. Since an exception has -- been raised, the thread's stack will certainly be below its limit -- again, but the programmer should take remedial action immediately. StackOverflow :: AsyncException -- | The program's heap is reaching its limit, and the program should take -- action to reduce the amount of live data it has. Notes: -- --
-- throw e `seq` x ===> throw e -- throwIO e `seq` x ===> x ---- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwIO will only cause -- an exception to be raised when it is used within the IO monad. -- The throwIO variant should be used in preference to -- throw to raise an exception within the IO monad because -- it guarantees ordering with respect to other IO operations, -- whereas throw does not. throwIO :: Exception e => e -> IO a -- | Throw an exception. Exceptions may be thrown from purely functional -- code, but may only be caught within the IO monad. throw :: Exception e => e -> a -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. This is a useful property to -- know when dealing with race conditions: eg. if there are two threads -- that can kill each other, it is guaranteed that only one of the -- threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () -- | This is the simplest of the exception-catching functions. It takes a -- single argument, runs it, and if an exception is raised the "handler" -- is executed, with the value of the exception passed as an argument. -- Otherwise, the result is returned as normal. For example: -- --
-- catch (readFile f) -- (\e -> do let err = show (e :: IOException) -- hPutStr stderr ("Warning: Couldn't open " ++ f ++ ": " ++ err) -- return "") ---- -- Note that we have to give a type signature to e, or the -- program will not typecheck as the type is ambiguous. While it is -- possible to catch exceptions of any type, see the section "Catching -- all exceptions" (in Control.Exception) for an explanation of -- the problems with doing so. -- -- For catching exceptions in pure (non-IO) expressions, see the -- function evaluate. -- -- Note that due to Haskell's unspecified evaluation order, an expression -- may throw one of several possible exceptions: consider the expression -- (error "urk") + (1 `div` 0). Does the expression throw -- ErrorCall "urk", or DivideByZero? -- -- The answer is "it might throw either"; the choice is -- non-deterministic. If you are catching any type of exception then you -- might catch either. If you are calling catch with type IO -- Int -> (ArithException -> IO Int) -> IO Int then the -- handler may get run with DivideByZero as an argument, or an -- ErrorCall "urk" exception may be propogated further up. If -- you call it again, you might get a the opposite behaviour. This is ok, -- because catch is an IO computation. -- -- Note that the Prelude also exports a function called -- catch with a similar type to catch, except that the -- Prelude version only catches the IO and user families of -- exceptions (as required by Haskell 98). -- -- We recommend either hiding the Prelude version of catch -- when importing Control.Exception: -- --
-- import Prelude hiding (catch) ---- -- or importing Control.Exception qualified, to avoid -- name-clashes: -- --
-- import qualified Control.Exception as C ---- -- and then using C.catch catch :: Exception e => IO a -> (e -> IO a) -> IO a -- | The function catchJust is like catch, but it takes an -- extra argument which is an exception predicate, a function -- which selects which type of exceptions we're interested in. -- --
-- catchJust (\e -> if isDoesNotExistErrorType (ioeGetErrorType e) then Just () else Nothing) -- (readFile f) -- (\_ -> do hPutStrLn stderr ("No such file: " ++ show f) -- return "") ---- -- Any other exceptions which are not matched by the predicate are -- re-raised, and may be caught by an enclosing catch, -- catchJust, etc. catchJust :: Exception e => (e -> Maybe b) -> IO a -> (b -> IO a) -> IO a -- | A version of catch with the arguments swapped around; useful in -- situations where the code for the handler is shorter. For example: -- --
-- do handle (\NonTermination -> exitWith (ExitFailure 1)) $ -- ... --handle :: Exception e => (e -> IO a) -> IO a -> IO a -- | A version of catchJust with the arguments swapped around (see -- handle). handleJust :: Exception e => (e -> Maybe b) -> (b -> IO a) -> IO a -> IO a -- | Similar to catch, but returns an Either result which is -- (Right a) if no exception of type e was -- raised, or (Left ex) if an exception of type -- e was raised and its value is ex. If any other type -- of exception is raised than it will be propogated up to the next -- enclosing exception handler. -- --
-- try a = catch (Right `liftM` a) (return . Left) ---- -- Note that System.IO.Error also exports a function called -- try with a similar type to try, except that it catches -- only the IO and user families of exceptions (as required by the -- Haskell 98 IO module). try :: Exception e => IO a -> IO (Either e a) -- | A variant of try that takes an exception predicate to select -- which exceptions are caught (c.f. catchJust). If the exception -- does not match the predicate, it is re-thrown. tryJust :: Exception e => (e -> Maybe b) -> IO a -> IO (Either b a) -- | Like finally, but only performs the final action if there was -- an exception raised by the computation. onException :: IO a -> IO b -> IO a -- | Forces its argument to be evaluated to weak head normal form when the -- resultant IO action is executed. It can be used to order -- evaluation with respect to other IO operations; its semantics -- are given by -- --
-- evaluate x `seq` y ==> y -- evaluate x `catch` f ==> (return $! x) `catch` f -- evaluate x >>= f ==> (return $! x) >>= f ---- -- Note: the first equation implies that (evaluate x) is -- not the same as (return $! x). A correct definition is -- --
-- evaluate x = (return $! x) >>= return --evaluate :: a -> IO a -- | This function maps one exception into another as proposed in the paper -- "A semantics for imprecise exceptions". mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a -- | Executes an IO computation with asynchronous exceptions masked. -- That is, any thread which attempts to raise an exception in the -- current thread with throwTo will be blocked until asynchronous -- exceptions are unmasked again. -- -- The argument passed to mask is a function that takes as its -- argument another function, which can be used to restore the prevailing -- masking state within the context of the masked computation. For -- example, a common way to use mask is to protect the acquisition -- of a resource: -- --
-- mask $ \restore -> do -- x <- acquire -- restore (do_something_with x) `onException` release -- release ---- -- This code guarantees that acquire is paired with -- release, by masking asynchronous exceptions for the critical -- parts. (Rather than write this code yourself, it would be better to -- use bracket which abstracts the general pattern). -- -- Note that the restore action passed to the argument to -- mask does not necessarily unmask asynchronous exceptions, it -- just restores the masking state to that of the enclosing context. Thus -- if asynchronous exceptions are already masked, mask cannot be -- used to unmask exceptions again. This is so that if you call a library -- function with exceptions masked, you can be sure that the library call -- will not be able to unmask exceptions again. If you are writing -- library code and need to use asynchronous exceptions, the only way is -- to create a new thread; see forkIOWithUnmask. -- -- Asynchronous exceptions may still be received while in the masked -- state if the masked thread blocks in certain ways; see -- Control.Exception#interruptible. -- -- Threads created by forkIO inherit the masked state from the -- parent; that is, to start a thread in blocked mode, use mask_ $ -- forkIO .... This is particularly useful if you need to establish -- an exception handler in the forked thread before any asynchronous -- exceptions are received. To create a a new thread in an unmasked state -- use forkIOUnmasked. mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b -- | Like mask, but does not pass a restore action to the -- argument. mask_ :: IO a -> IO a -- | Like mask, but the masked computation is not interruptible (see -- Control.Exception#interruptible). THIS SHOULD BE USED WITH -- GREAT CARE, because if a thread executing in -- uninterruptibleMask blocks for any reason, then the thread (and -- possibly the program, if this is the main thread) will be unresponsive -- and unkillable. This function should only be necessary if you need to -- mask exceptions around an interruptible operation, and you can -- guarantee that the interruptible operation will only block for a short -- period of time. uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b -- | Like uninterruptibleMask, but does not pass a restore -- action to the argument. uninterruptibleMask_ :: IO a -> IO a -- | Describes the behaviour of a thread when an asynchronous exception is -- received. data MaskingState -- | asynchronous exceptions are unmasked (the normal state) Unmasked :: MaskingState -- | the state during mask: asynchronous exceptions are masked, but -- blocking operations may still be interrupted MaskedInterruptible :: MaskingState -- | the state during uninterruptibleMask: asynchronous exceptions -- are masked, and blocking operations may not be interrupted MaskedUninterruptible :: MaskingState -- | Returns the MaskingState for the current thread. getMaskingState :: IO MaskingState -- | Note: this function is deprecated, please use mask instead. -- -- Applying block to a computation will execute that computation -- with asynchronous exceptions blocked. That is, any thread which -- attempts to raise an exception in the current thread with -- throwTo will be blocked until asynchronous exceptions are -- unblocked again. There's no need to worry about re-enabling -- asynchronous exceptions; that is done automatically on exiting the -- scope of block. -- -- Threads created by forkIO inherit the blocked state from the -- parent; that is, to start a thread in blocked mode, use block $ -- forkIO .... This is particularly useful if you need to establish -- an exception handler in the forked thread before any asynchronous -- exceptions are received. block :: IO a -> IO a -- | Note: this function is deprecated, please use mask instead. -- -- To re-enable asynchronous exceptions inside the scope of block, -- unblock can be used. It scopes in exactly the same way, so on -- exit from unblock asynchronous exception delivery will be -- disabled again. unblock :: IO a -> IO a -- | returns True if asynchronous exceptions are blocked in the current -- thread. blocked :: IO Bool -- | If the first argument evaluates to True, then the result is the -- second argument. Otherwise an AssertionFailed exception is -- raised, containing a String with the source file and line -- number of the call to assert. -- -- Assertions can normally be turned on or off with a compiler flag (for -- GHC, assertions are normally on unless optimisation is turned on with -- -O or the -fignore-asserts option is given). When -- assertions are turned off, the first argument to assert is -- ignored, and the second argument is returned as the result. assert :: Bool -> a -> a -- | When you want to acquire a resource, do some work with it, and then -- release the resource, it is a good idea to use bracket, because -- bracket will install the necessary exception handler to release -- the resource in the event that an exception is raised during the -- computation. If an exception is raised, then bracket will -- re-raise the exception (after performing the release). -- -- A common example is opening a file: -- --
-- bracket -- (openFile "filename" ReadMode) -- (hClose) -- (\fileHandle -> do { ... }) ---- -- The arguments to bracket are in this order so that we can -- partially apply it, e.g.: -- --
-- withFile name mode = bracket (openFile name mode) hClose --bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c -- | A variant of bracket where the return value from the first -- computation is not required. bracket_ :: IO a -> IO b -> IO c -> IO c -- | Like bracket, but only performs the final action if there was -- an exception raised by the in-between computation. bracketOnError :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c -- | A specialised variant of bracket with just a computation to run -- afterward. finally :: IO a -> IO b -> IO a recSelError :: Addr# -> a recConError :: Addr# -> a irrefutPatError :: Addr# -> a runtimeError :: Addr# -> a nonExhaustiveGuardsError :: Addr# -> a patError :: Addr# -> a noMethodBindingError :: Addr# -> a absentError :: Addr# -> a nonTermination :: SomeException nestedAtomically :: SomeException instance Typeable NestedAtomically instance Typeable NonTermination instance Typeable NoMethodError instance Typeable RecUpdError instance Typeable RecConError instance Typeable RecSelError instance Typeable PatternMatchFail instance Exception NestedAtomically instance Show NestedAtomically instance Exception NonTermination instance Show NonTermination instance Exception NoMethodError instance Show NoMethodError instance Exception RecUpdError instance Show RecUpdError instance Exception RecConError instance Show RecConError instance Exception RecSelError instance Show RecSelError instance Exception PatternMatchFail instance Show PatternMatchFail -- | An MVar t is mutable location that is either empty or -- contains a value of type t. It has two fundamental -- operations: putMVar which fills an MVar if it is empty -- and blocks otherwise, and takeMVar which empties an MVar -- if it is full and blocks otherwise. They can be used in multiple -- different ways: -- --
-- data SkipChan a = SkipChan (MVar (a, [MVar ()])) (MVar ()) -- -- newSkipChan :: IO (SkipChan a) -- newSkipChan = do -- sem <- newEmptyMVar -- main <- newMVar (undefined, [sem]) -- return (SkipChan main sem) -- -- putSkipChan :: SkipChan a -> a -> IO () -- putSkipChan (SkipChan main _) v = do -- (_, sems) <- takeMVar main -- putMVar main (v, []) -- mapM_ (sem -> putMVar sem ()) sems -- -- getSkipChan :: SkipChan a -> IO a -- getSkipChan (SkipChan main sem) = do -- takeMVar sem -- (v, sems) <- takeMVar main -- putMVar main (v, sem:sems) -- return v -- -- dupSkipChan :: SkipChan a -> IO (SkipChan a) -- dupSkipChan (SkipChan main _) = do -- sem <- newEmptyMVar -- (v, sems) <- takeMVar main -- putMVar main (v, sem:sems) -- return (SkipChan main sem) ---- -- This example was adapted from the original Concurrent Haskell paper. -- For more examples of MVars being used to build higher-level -- synchronization primitives, see Chan and QSem. module Control.Concurrent.MVar -- | An MVar (pronounced "em-var") is a synchronising variable, used -- for communication between concurrent threads. It can be thought of as -- a a box, which may be empty or full. data MVar a -- | Create an MVar which is initially empty. newEmptyMVar :: IO (MVar a) -- | Create an MVar which contains the supplied value. newMVar :: a -> IO (MVar a) -- | Return the contents of the MVar. If the MVar is -- currently empty, takeMVar will wait until it is full. After a -- takeMVar, the MVar is left empty. -- -- There are two further important properties of takeMVar: -- --
-- data MyException = ThisException | ThatException -- deriving (Show, Typeable) -- -- instance Exception MyException ---- -- The default method definitions in the Exception class do what -- we need in this case. You can now throw and catch -- ThisException and ThatException as exceptions: -- --
-- *Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) -- Caught ThisException ---- -- In more complicated examples, you may wish to define a whole hierarchy -- of exceptions: -- --
-- --------------------------------------------------------------------- -- -- Make the root exception type for all the exceptions in a compiler -- -- data SomeCompilerException = forall e . Exception e => SomeCompilerException e -- deriving Typeable -- -- instance Show SomeCompilerException where -- show (SomeCompilerException e) = show e -- -- instance Exception SomeCompilerException -- -- compilerExceptionToException :: Exception e => e -> SomeException -- compilerExceptionToException = toException . SomeCompilerException -- -- compilerExceptionFromException :: Exception e => SomeException -> Maybe e -- compilerExceptionFromException x = do -- SomeCompilerException a <- fromException x -- cast a -- -- --------------------------------------------------------------------- -- -- Make a subhierarchy for exceptions in the frontend of the compiler -- -- data SomeFrontendException = forall e . Exception e => SomeFrontendException e -- deriving Typeable -- -- instance Show SomeFrontendException where -- show (SomeFrontendException e) = show e -- -- instance Exception SomeFrontendException where -- toException = compilerExceptionToException -- fromException = compilerExceptionFromException -- -- frontendExceptionToException :: Exception e => e -> SomeException -- frontendExceptionToException = toException . SomeFrontendException -- -- frontendExceptionFromException :: Exception e => SomeException -> Maybe e -- frontendExceptionFromException x = do -- SomeFrontendException a <- fromException x -- cast a -- -- --------------------------------------------------------------------- -- -- Make an exception type for a particular frontend compiler exception -- -- data MismatchedParentheses = MismatchedParentheses -- deriving (Typeable, Show) -- -- instance Exception MismatchedParentheses where -- toException = frontendExceptionToException -- fromException = frontendExceptionFromException ---- -- We can now catch a MismatchedParentheses exception as -- MismatchedParentheses, SomeFrontendException or -- SomeCompilerException, but not other types, e.g. -- IOException: -- --
-- *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) -- Caught MismatchedParentheses -- *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) -- Caught MismatchedParentheses -- *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) -- Caught MismatchedParentheses -- *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException)) -- *** Exception: MismatchedParentheses --class (Typeable e, Show e) => Exception e where toException = SomeException fromException (SomeException e) = cast e toException :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Exceptions that occur in the IO monad. An -- IOException records a more specific error type, a descriptive -- string and maybe the handle that was used when the error was flagged. data IOException -- | Arithmetic exceptions. data ArithException Overflow :: ArithException Underflow :: ArithException LossOfPrecision :: ArithException DivideByZero :: ArithException Denormal :: ArithException -- | Exceptions generated by array operations data ArrayException -- | An attempt was made to index an array outside its declared bounds. IndexOutOfBounds :: String -> ArrayException -- | An attempt was made to evaluate an element of an array that had not -- been initialized. UndefinedElement :: String -> ArrayException -- | assert was applied to False. data AssertionFailed AssertionFailed :: String -> AssertionFailed -- | Asynchronous exceptions. data AsyncException -- | The current thread's stack exceeded its limit. Since an exception has -- been raised, the thread's stack will certainly be below its limit -- again, but the programmer should take remedial action immediately. StackOverflow :: AsyncException -- | The program's heap is reaching its limit, and the program should take -- action to reduce the amount of live data it has. Notes: -- --
-- throw e `seq` x ===> throw e -- throwIO e `seq` x ===> x ---- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwIO will only cause -- an exception to be raised when it is used within the IO monad. -- The throwIO variant should be used in preference to -- throw to raise an exception within the IO monad because -- it guarantees ordering with respect to other IO operations, -- whereas throw does not. throwIO :: Exception e => e -> IO a -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. This is a useful property to -- know when dealing with race conditions: eg. if there are two threads -- that can kill each other, it is guaranteed that only one of the -- threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () -- | This is the simplest of the exception-catching functions. It takes a -- single argument, runs it, and if an exception is raised the "handler" -- is executed, with the value of the exception passed as an argument. -- Otherwise, the result is returned as normal. For example: -- --
-- catch (readFile f) -- (\e -> do let err = show (e :: IOException) -- hPutStr stderr ("Warning: Couldn't open " ++ f ++ ": " ++ err) -- return "") ---- -- Note that we have to give a type signature to e, or the -- program will not typecheck as the type is ambiguous. While it is -- possible to catch exceptions of any type, see the section "Catching -- all exceptions" (in Control.Exception) for an explanation of -- the problems with doing so. -- -- For catching exceptions in pure (non-IO) expressions, see the -- function evaluate. -- -- Note that due to Haskell's unspecified evaluation order, an expression -- may throw one of several possible exceptions: consider the expression -- (error "urk") + (1 `div` 0). Does the expression throw -- ErrorCall "urk", or DivideByZero? -- -- The answer is "it might throw either"; the choice is -- non-deterministic. If you are catching any type of exception then you -- might catch either. If you are calling catch with type IO -- Int -> (ArithException -> IO Int) -> IO Int then the -- handler may get run with DivideByZero as an argument, or an -- ErrorCall "urk" exception may be propogated further up. If -- you call it again, you might get a the opposite behaviour. This is ok, -- because catch is an IO computation. -- -- Note that the Prelude also exports a function called -- catch with a similar type to catch, except that the -- Prelude version only catches the IO and user families of -- exceptions (as required by Haskell 98). -- -- We recommend either hiding the Prelude version of catch -- when importing Control.Exception: -- --
-- import Prelude hiding (catch) ---- -- or importing Control.Exception qualified, to avoid -- name-clashes: -- --
-- import qualified Control.Exception as C ---- -- and then using C.catch catch :: Exception e => IO a -> (e -> IO a) -> IO a -- | Sometimes you want to catch two different sorts of exception. You -- could do something like -- --
-- f = expr `catch` \ (ex :: ArithException) -> handleArith ex -- `catch` \ (ex :: IOException) -> handleIO ex ---- -- However, there are a couple of problems with this approach. The first -- is that having two exception handlers is inefficient. However, the -- more serious issue is that the second exception handler will catch -- exceptions in the first, e.g. in the example above, if -- handleArith throws an IOException then the second -- exception handler will catch it. -- -- Instead, we provide a function catches, which would be used -- thus: -- --
-- f = expr `catches` [Handler (\ (ex :: ArithException) -> handleArith ex), -- Handler (\ (ex :: IOException) -> handleIO ex)] --catches :: IO a -> [Handler a] -> IO a -- | You need this when using catches. data Handler a Handler :: (e -> IO a) -> Handler a -- | The function catchJust is like catch, but it takes an -- extra argument which is an exception predicate, a function -- which selects which type of exceptions we're interested in. -- --
-- catchJust (\e -> if isDoesNotExistErrorType (ioeGetErrorType e) then Just () else Nothing) -- (readFile f) -- (\_ -> do hPutStrLn stderr ("No such file: " ++ show f) -- return "") ---- -- Any other exceptions which are not matched by the predicate are -- re-raised, and may be caught by an enclosing catch, -- catchJust, etc. catchJust :: Exception e => (e -> Maybe b) -> IO a -> (b -> IO a) -> IO a -- | A version of catch with the arguments swapped around; useful in -- situations where the code for the handler is shorter. For example: -- --
-- do handle (\NonTermination -> exitWith (ExitFailure 1)) $ -- ... --handle :: Exception e => (e -> IO a) -> IO a -> IO a -- | A version of catchJust with the arguments swapped around (see -- handle). handleJust :: Exception e => (e -> Maybe b) -> (b -> IO a) -> IO a -> IO a -- | Similar to catch, but returns an Either result which is -- (Right a) if no exception of type e was -- raised, or (Left ex) if an exception of type -- e was raised and its value is ex. If any other type -- of exception is raised than it will be propogated up to the next -- enclosing exception handler. -- --
-- try a = catch (Right `liftM` a) (return . Left) ---- -- Note that System.IO.Error also exports a function called -- try with a similar type to try, except that it catches -- only the IO and user families of exceptions (as required by the -- Haskell 98 IO module). try :: Exception e => IO a -> IO (Either e a) -- | A variant of try that takes an exception predicate to select -- which exceptions are caught (c.f. catchJust). If the exception -- does not match the predicate, it is re-thrown. tryJust :: Exception e => (e -> Maybe b) -> IO a -> IO (Either b a) -- | Forces its argument to be evaluated to weak head normal form when the -- resultant IO action is executed. It can be used to order -- evaluation with respect to other IO operations; its semantics -- are given by -- --
-- evaluate x `seq` y ==> y -- evaluate x `catch` f ==> (return $! x) `catch` f -- evaluate x >>= f ==> (return $! x) >>= f ---- -- Note: the first equation implies that (evaluate x) is -- not the same as (return $! x). A correct definition is -- --
-- evaluate x = (return $! x) >>= return --evaluate :: a -> IO a -- | This function maps one exception into another as proposed in the paper -- "A semantics for imprecise exceptions". mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a -- | Executes an IO computation with asynchronous exceptions masked. -- That is, any thread which attempts to raise an exception in the -- current thread with throwTo will be blocked until asynchronous -- exceptions are unmasked again. -- -- The argument passed to mask is a function that takes as its -- argument another function, which can be used to restore the prevailing -- masking state within the context of the masked computation. For -- example, a common way to use mask is to protect the acquisition -- of a resource: -- --
-- mask $ \restore -> do -- x <- acquire -- restore (do_something_with x) `onException` release -- release ---- -- This code guarantees that acquire is paired with -- release, by masking asynchronous exceptions for the critical -- parts. (Rather than write this code yourself, it would be better to -- use bracket which abstracts the general pattern). -- -- Note that the restore action passed to the argument to -- mask does not necessarily unmask asynchronous exceptions, it -- just restores the masking state to that of the enclosing context. Thus -- if asynchronous exceptions are already masked, mask cannot be -- used to unmask exceptions again. This is so that if you call a library -- function with exceptions masked, you can be sure that the library call -- will not be able to unmask exceptions again. If you are writing -- library code and need to use asynchronous exceptions, the only way is -- to create a new thread; see forkIOWithUnmask. -- -- Asynchronous exceptions may still be received while in the masked -- state if the masked thread blocks in certain ways; see -- Control.Exception#interruptible. -- -- Threads created by forkIO inherit the masked state from the -- parent; that is, to start a thread in blocked mode, use mask_ $ -- forkIO .... This is particularly useful if you need to establish -- an exception handler in the forked thread before any asynchronous -- exceptions are received. To create a a new thread in an unmasked state -- use forkIOUnmasked. mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b -- | Like mask, but does not pass a restore action to the -- argument. mask_ :: IO a -> IO a -- | Like mask, but the masked computation is not interruptible (see -- Control.Exception#interruptible). THIS SHOULD BE USED WITH -- GREAT CARE, because if a thread executing in -- uninterruptibleMask blocks for any reason, then the thread (and -- possibly the program, if this is the main thread) will be unresponsive -- and unkillable. This function should only be necessary if you need to -- mask exceptions around an interruptible operation, and you can -- guarantee that the interruptible operation will only block for a short -- period of time. uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b -- | Like uninterruptibleMask, but does not pass a restore -- action to the argument. uninterruptibleMask_ :: IO a -> IO a -- | Describes the behaviour of a thread when an asynchronous exception is -- received. data MaskingState -- | asynchronous exceptions are unmasked (the normal state) Unmasked :: MaskingState -- | the state during mask: asynchronous exceptions are masked, but -- blocking operations may still be interrupted MaskedInterruptible :: MaskingState -- | the state during uninterruptibleMask: asynchronous exceptions -- are masked, and blocking operations may not be interrupted MaskedUninterruptible :: MaskingState -- | Returns the MaskingState for the current thread. getMaskingState :: IO MaskingState -- | When invoked inside mask, this function allows a blocked -- asynchronous exception to be raised, if one exists. It is equivalent -- to performing an interruptible operation (see ), but does not involve -- any actual blocking. -- -- When called outside mask, or inside uninterruptibleMask, -- this function has no effect. allowInterrupt :: IO () -- | Note: this function is deprecated, please use mask instead. -- -- Applying block to a computation will execute that computation -- with asynchronous exceptions blocked. That is, any thread which -- attempts to raise an exception in the current thread with -- throwTo will be blocked until asynchronous exceptions are -- unblocked again. There's no need to worry about re-enabling -- asynchronous exceptions; that is done automatically on exiting the -- scope of block. -- -- Threads created by forkIO inherit the blocked state from the -- parent; that is, to start a thread in blocked mode, use block $ -- forkIO .... This is particularly useful if you need to establish -- an exception handler in the forked thread before any asynchronous -- exceptions are received. block :: IO a -> IO a -- | Note: this function is deprecated, please use mask instead. -- -- To re-enable asynchronous exceptions inside the scope of block, -- unblock can be used. It scopes in exactly the same way, so on -- exit from unblock asynchronous exception delivery will be -- disabled again. unblock :: IO a -> IO a -- | returns True if asynchronous exceptions are blocked in the current -- thread. blocked :: IO Bool -- | If the first argument evaluates to True, then the result is the -- second argument. Otherwise an AssertionFailed exception is -- raised, containing a String with the source file and line -- number of the call to assert. -- -- Assertions can normally be turned on or off with a compiler flag (for -- GHC, assertions are normally on unless optimisation is turned on with -- -O or the -fignore-asserts option is given). When -- assertions are turned off, the first argument to assert is -- ignored, and the second argument is returned as the result. assert :: Bool -> a -> a -- | When you want to acquire a resource, do some work with it, and then -- release the resource, it is a good idea to use bracket, because -- bracket will install the necessary exception handler to release -- the resource in the event that an exception is raised during the -- computation. If an exception is raised, then bracket will -- re-raise the exception (after performing the release). -- -- A common example is opening a file: -- --
-- bracket -- (openFile "filename" ReadMode) -- (hClose) -- (\fileHandle -> do { ... }) ---- -- The arguments to bracket are in this order so that we can -- partially apply it, e.g.: -- --
-- withFile name mode = bracket (openFile name mode) hClose --bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c -- | A variant of bracket where the return value from the first -- computation is not required. bracket_ :: IO a -> IO b -> IO c -> IO c -- | Like bracket, but only performs the final action if there was -- an exception raised by the in-between computation. bracketOnError :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c -- | A specialised variant of bracket with just a computation to run -- afterward. finally :: IO a -> IO b -> IO a -- | Like finally, but only performs the final action if there was -- an exception raised by the computation. onException :: IO a -> IO b -> IO a -- | "Unsafe" IO operations. module System.IO.Unsafe -- | This is the "back door" into the IO monad, allowing IO -- computation to be performed at any time. For this to be safe, the -- IO computation should be free of side effects and independent -- of its environment. -- -- If the I/O computation wrapped in unsafePerformIO performs side -- effects, then the relative order in which those side effects take -- place (relative to the main I/O trunk, or other calls to -- unsafePerformIO) is indeterminate. Furthermore, when using -- unsafePerformIO to cause side-effects, you should take the -- following precautions to ensure the side effects are performed as many -- times as you expect them to be. Note that these precautions are -- necessary for GHC, but may not be sufficient, and other compilers may -- require different precautions: -- --
-- test :: IORef [a] -- test = unsafePerformIO $ newIORef [] -- -- main = do -- writeIORef test [42] -- bang <- readIORef test -- print (bang :: [Char]) ---- -- This program will core dump. This problem with polymorphic references -- is well known in the ML community, and does not arise with normal -- monadic use of references. There is no easy way to make it impossible -- once you use unsafePerformIO. Indeed, it is possible to write -- coerce :: a -> b with the help of unsafePerformIO. -- So be careful! unsafePerformIO :: IO a -> a -- | This version of unsafePerformIO is more efficient because it -- omits the check that the IO is only being performed by a single -- thread. Hence, when you use unsafeDupablePerformIO, there is a -- possibility that the IO action may be performed multiple times (on a -- multiprocessor), and you should therefore ensure that it gives the -- same results each time. unsafeDupablePerformIO :: IO a -> a -- | unsafeInterleaveIO allows IO computation to be deferred -- lazily. When passed a value of type IO a, the IO will -- only be performed when the value of the a is demanded. This -- is used to implement lazy file reading, see hGetContents. unsafeInterleaveIO :: IO a -> IO a -- | A slightly faster version of fixIO that may not be safe to use -- with multiple threads. The unsafety arises when used like this: -- --
-- unsafeFixIO $ \r -> -- forkIO (print r) -- return (...) ---- -- In this case, the child thread will receive a NonTermination -- exception instead of waiting for the value of r to be -- computed. unsafeFixIO :: (a -> IO a) -> IO a -- | Standard IO Errors. module System.IO.Error -- | The Haskell 98 type for exceptions in the IO monad. Any I/O -- operation may raise an IOError instead of returning a result. -- For a more general type of exception, including also those that arise -- in pure code, see Control.Exception.Exception. -- -- In Haskell 98, this is an opaque type. type IOError = IOException -- | Construct an IOError value with a string describing the error. -- The fail method of the IO instance of the Monad -- class raises a userError, thus: -- --
-- instance Monad IO where -- ... -- fail s = ioError (userError s) --userError :: String -> IOError -- | Construct an IOError of the given type where the second -- argument describes the error location and the third and fourth -- argument contain the file handle and file path of the file involved in -- the error if applicable. mkIOError :: IOErrorType -> String -> Maybe Handle -> Maybe FilePath -> IOError -- | Adds a location description and maybe a file path and file handle to -- an IOError. If any of the file handle or file path is not given -- the corresponding value in the IOError remains unaltered. annotateIOError :: IOError -> String -> Maybe Handle -> Maybe FilePath -> IOError -- | An error indicating that an IO operation failed because one of -- its arguments already exists. isAlreadyExistsError :: IOError -> Bool -- | An error indicating that an IO operation failed because one of -- its arguments does not exist. isDoesNotExistError :: IOError -> Bool -- | An error indicating that an IO operation failed because one of -- its arguments is a single-use resource, which is already being used -- (for example, opening the same file twice for writing might give this -- error). isAlreadyInUseError :: IOError -> Bool -- | An error indicating that an IO operation failed because the -- device is full. isFullError :: IOError -> Bool -- | An error indicating that an IO operation failed because the end -- of file has been reached. isEOFError :: IOError -> Bool -- | An error indicating that an IO operation failed because the -- operation was not possible. Any computation which returns an IO -- result may fail with isIllegalOperation. In some cases, an -- implementation will not be able to distinguish between the possible -- error causes. In this case it should fail with -- isIllegalOperation. isIllegalOperation :: IOError -> Bool -- | An error indicating that an IO operation failed because the -- user does not have sufficient operating system privilege to perform -- that operation. isPermissionError :: IOError -> Bool -- | A programmer-defined error value constructed using userError. isUserError :: IOError -> Bool ioeGetErrorType :: IOError -> IOErrorType ioeGetLocation :: IOError -> String ioeGetErrorString :: IOError -> String ioeGetHandle :: IOError -> Maybe Handle ioeGetFileName :: IOError -> Maybe FilePath ioeSetErrorType :: IOError -> IOErrorType -> IOError ioeSetErrorString :: IOError -> String -> IOError ioeSetLocation :: IOError -> String -> IOError ioeSetHandle :: IOError -> Handle -> IOError ioeSetFileName :: IOError -> FilePath -> IOError -- | An abstract type that contains a value for each variant of -- IOError. data IOErrorType -- | I/O error where the operation failed because one of its arguments -- already exists. alreadyExistsErrorType :: IOErrorType -- | I/O error where the operation failed because one of its arguments does -- not exist. doesNotExistErrorType :: IOErrorType -- | I/O error where the operation failed because one of its arguments is a -- single-use resource, which is already being used. alreadyInUseErrorType :: IOErrorType -- | I/O error where the operation failed because the device is full. fullErrorType :: IOErrorType -- | I/O error where the operation failed because the end of file has been -- reached. eofErrorType :: IOErrorType -- | I/O error where the operation is not possible. illegalOperationErrorType :: IOErrorType -- | I/O error where the operation failed because the user does not have -- sufficient operating system privilege to perform that operation. permissionErrorType :: IOErrorType -- | I/O error that is programmer-defined. userErrorType :: IOErrorType -- | I/O error where the operation failed because one of its arguments -- already exists. isAlreadyExistsErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because one of its arguments does -- not exist. isDoesNotExistErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because one of its arguments is a -- single-use resource, which is already being used. isAlreadyInUseErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because the device is full. isFullErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because the end of file has been -- reached. isEOFErrorType :: IOErrorType -> Bool -- | I/O error where the operation is not possible. isIllegalOperationErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because the user does not have -- sufficient operating system privilege to perform that operation. isPermissionErrorType :: IOErrorType -> Bool -- | I/O error that is programmer-defined. isUserErrorType :: IOErrorType -> Bool -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | The catchIOError function establishes a handler that receives -- any IOError raised in the action protected by -- catchIOError. An IOError is caught by the most recent -- handler established by one of the exception handling functions. These -- handlers are not selective: all IOErrors are caught. Exception -- propagation must be explicitly provided in a handler by re-raising any -- unwanted exceptions. For example, in -- --
-- f = catchIOError g (\e -> if IO.isEOFError e then return [] else ioError e) ---- -- the function f returns [] when an end-of-file -- exception (cf. isEOFError) occurs in g; otherwise, the -- exception is propagated to the next outer handler. -- -- When an exception propagates outside the main program, the Haskell -- system prints the associated IOError value and exits the -- program. -- -- Non-I/O exceptions are not caught by this variant; to catch all -- exceptions, use catch from Control.Exception. catchIOError :: IO a -> (IOError -> IO a) -> IO a -- | The catch function is deprecated. Please use the new exceptions -- variant, catch from Control.Exception, instead. -- | Deprecated: Please use the new exceptions variant, -- Control.Exception.catch catch :: IO a -> (IOError -> IO a) -> IO a -- | The construct tryIOError comp exposes IO errors which -- occur within a computation, and which are not fully handled. -- -- Non-I/O exceptions are not caught by this variant; to catch all -- exceptions, use try from Control.Exception. tryIOError :: IO a -> IO (Either IOError a) -- | The try function is deprecated. Please use the new exceptions -- variant, try from Control.Exception, instead. -- | Deprecated: Please use the new exceptions variant, -- Control.Exception.try try :: IO a -> IO (Either IOError a) -- | Catch any IOError that occurs in the computation and throw a -- modified version. modifyIOError :: (IOError -> IOError) -> IO a -> IO a module GHC.Conc.Signal type Signal = CInt type HandlerFun = ForeignPtr Word8 -> IO () setHandler :: Signal -> Maybe (HandlerFun, Dynamic) -> IO (Maybe (HandlerFun, Dynamic)) runHandlers :: ForeignPtr Word8 -> Signal -> IO () -- | POSIX data types: Haskell equivalents of the types defined by the -- <sys/types.h> C header on a POSIX system. module System.Posix.Types newtype CDev CDev :: Word64 -> CDev newtype CIno CIno :: Word64 -> CIno newtype CMode CMode :: Word32 -> CMode newtype COff COff :: Int64 -> COff newtype CPid CPid :: Int32 -> CPid newtype CSsize CSsize :: Int64 -> CSsize newtype CGid CGid :: Word32 -> CGid newtype CNlink CNlink :: Word64 -> CNlink newtype CUid CUid :: Word32 -> CUid newtype CCc CCc :: Word8 -> CCc newtype CSpeed CSpeed :: Word32 -> CSpeed newtype CTcflag CTcflag :: Word32 -> CTcflag newtype CRLim CRLim :: Word64 -> CRLim newtype Fd Fd :: CInt -> Fd type LinkCount = CNlink type UserID = CUid type GroupID = CGid type ByteCount = CSize type ClockTick = CClock type EpochTime = CTime type FileOffset = COff type ProcessID = CPid type ProcessGroupID = CPid type DeviceID = CDev type FileID = CIno type FileMode = CMode type Limit = CLong instance Typeable Fd instance Typeable CRLim instance Typeable CTcflag instance Typeable CSpeed instance Typeable CCc instance Typeable CUid instance Typeable CNlink instance Typeable CGid instance Typeable CSsize instance Typeable CPid instance Typeable COff instance Typeable CMode instance Typeable CIno instance Typeable CDev instance Eq CDev instance Ord CDev instance Num CDev instance Enum CDev instance Storable CDev instance Real CDev instance Eq CIno instance Ord CIno instance Num CIno instance Enum CIno instance Storable CIno instance Real CIno instance Bounded CIno instance Integral CIno instance Bits CIno instance Eq CMode instance Ord CMode instance Num CMode instance Enum CMode instance Storable CMode instance Real CMode instance Bounded CMode instance Integral CMode instance Bits CMode instance Eq COff instance Ord COff instance Num COff instance Enum COff instance Storable COff instance Real COff instance Bounded COff instance Integral COff instance Bits COff instance Eq CPid instance Ord CPid instance Num CPid instance Enum CPid instance Storable CPid instance Real CPid instance Bounded CPid instance Integral CPid instance Bits CPid instance Eq CSsize instance Ord CSsize instance Num CSsize instance Enum CSsize instance Storable CSsize instance Real CSsize instance Bounded CSsize instance Integral CSsize instance Bits CSsize instance Eq CGid instance Ord CGid instance Num CGid instance Enum CGid instance Storable CGid instance Real CGid instance Bounded CGid instance Integral CGid instance Bits CGid instance Eq CNlink instance Ord CNlink instance Num CNlink instance Enum CNlink instance Storable CNlink instance Real CNlink instance Bounded CNlink instance Integral CNlink instance Bits CNlink instance Eq CUid instance Ord CUid instance Num CUid instance Enum CUid instance Storable CUid instance Real CUid instance Bounded CUid instance Integral CUid instance Bits CUid instance Eq CCc instance Ord CCc instance Num CCc instance Enum CCc instance Storable CCc instance Real CCc instance Eq CSpeed instance Ord CSpeed instance Num CSpeed instance Enum CSpeed instance Storable CSpeed instance Real CSpeed instance Eq CTcflag instance Ord CTcflag instance Num CTcflag instance Enum CTcflag instance Storable CTcflag instance Real CTcflag instance Bounded CTcflag instance Integral CTcflag instance Bits CTcflag instance Eq CRLim instance Ord CRLim instance Num CRLim instance Enum CRLim instance Storable CRLim instance Real CRLim instance Bounded CRLim instance Integral CRLim instance Bits CRLim instance Eq Fd instance Ord Fd instance Num Fd instance Enum Fd instance Storable Fd instance Real Fd instance Bounded Fd instance Integral Fd instance Bits Fd instance Show Fd instance Read Fd instance Show CRLim instance Read CRLim instance Show CTcflag instance Read CTcflag instance Show CSpeed instance Read CSpeed instance Show CCc instance Read CCc instance Show CUid instance Read CUid instance Show CNlink instance Read CNlink instance Show CGid instance Read CGid instance Show CSsize instance Read CSsize instance Show CPid instance Read CPid instance Show COff instance Read COff instance Show CMode instance Read CMode instance Show CIno instance Read CIno instance Show CDev instance Read CDev module GHC.Fingerprint data Fingerprint Fingerprint :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> Fingerprint fingerprint0 :: Fingerprint fingerprintData :: Ptr Word8 -> Int -> IO Fingerprint fingerprintString :: String -> Fingerprint fingerprintFingerprints :: [Fingerprint] -> Fingerprint -- | A collection of data types, classes, and functions for interfacing -- with another programming language. -- -- Safe API Only. module Foreign.Safe -- | This module provides text encoding/decoding using iconv module GHC.IO.Encoding.Iconv iconvEncoding :: String -> IO TextEncoding mkIconvEncoding :: CodingFailureMode -> String -> IO TextEncoding localeEncodingName :: String -- | Text codecs for I/O module GHC.IO.Encoding data BufferCodec from to state BufferCodec :: (Buffer from -> Buffer to -> IO (CodingProgress, Buffer from, Buffer to)) -> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to)) -> IO () -> IO state -> (state -> IO ()) -> BufferCodec from to state -- | The encode function translates elements of the buffer -- from to the buffer to. It should translate as many -- elements as possible given the sizes of the buffers, including -- translating zero elements if there is either not enough room in -- to, or from does not contain a complete multibyte -- sequence. -- -- The fact that as many elements as possible are translated is used by -- the IO library in order to report translation errors at the point they -- actually occur, rather than when the buffer is translated. -- -- To allow us to use iconv as a BufferCode efficiently, character -- buffers are defined to contain lone surrogates instead of those -- private use characters that are used for roundtripping. Thus, Chars -- poked and peeked from a character buffer must undergo -- surrogatifyRoundtripCharacter and desurrogatifyRoundtripCharacter -- respectively. -- -- For more information on this, see Note [Roundtripping] in -- GHC.IO.Encoding.Failure. encode :: BufferCodec from to state -> Buffer from -> Buffer to -> IO (CodingProgress, Buffer from, Buffer to) -- | The recover function is used to continue decoding in the -- presence of invalid or unrepresentable sequences. This includes both -- those detected by encode returning InvalidSequence -- and those that occur because the input byte sequence appears to be -- truncated. -- -- Progress will usually be made by skipping the first element of the -- from buffer. This function should only be called if you are -- certain that you wish to do this skipping and if the to -- buffer has at least one element of free space. Because this function -- deals with decoding failure, it assumes that the from buffer has at -- least one element. -- -- recover may raise an exception rather than skipping anything. -- -- Currently, some implementations of recover may mutate the -- input buffer. In particular, this feature is used to implement -- transliteration. recover :: BufferCodec from to state -> Buffer from -> Buffer to -> IO (Buffer from, Buffer to) -- | Resources associated with the encoding may now be released. The -- encode function may not be called again after calling -- close. close :: BufferCodec from to state -> IO () -- | Return the current state of the codec. -- -- Many codecs are not stateful, and in these case the state can be -- represented as '()'. Other codecs maintain a state. For example, -- UTF-16 recognises a BOM (byte-order-mark) character at the beginning -- of the input, and remembers thereafter whether to use big-endian or -- little-endian mode. In this case, the state of the codec would include -- two pieces of information: whether we are at the beginning of the -- stream (the BOM only occurs at the beginning), and if not, whether to -- use the big or little-endian encoding. getState :: BufferCodec from to state -> IO state setState :: BufferCodec from to state -> state -> IO () -- | A TextEncoding is a specification of a conversion scheme -- between sequences of bytes and sequences of Unicode characters. -- -- For example, UTF-8 is an encoding of Unicode characters into a -- sequence of bytes. The TextEncoding for UTF-8 is utf8. data TextEncoding TextEncoding :: String -> IO (TextDecoder dstate) -> IO (TextEncoder estate) -> TextEncoding -- | a string that can be passed to mkTextEncoding to create an -- equivalent TextEncoding. textEncodingName :: TextEncoding -> String -- | Creates a means of decoding bytes into characters: the result must not -- be shared between several byte sequences or simultaneously across -- threads mkTextDecoder :: TextEncoding -> IO (TextDecoder dstate) -- | Creates a means of encode characters into bytes: the result must not -- be shared between several character sequences or simultaneously across -- threads mkTextEncoder :: TextEncoding -> IO (TextEncoder estate) type TextEncoder state = BufferCodec CharBufElem Word8 state type TextDecoder state = BufferCodec Word8 CharBufElem state data CodingProgress -- | Stopped because the input contains insufficient available elements, or -- all of the input sequence has been sucessfully translated. InputUnderflow :: CodingProgress -- | Stopped because the output contains insufficient free elements OutputUnderflow :: CodingProgress -- | Stopped because there are sufficient free elements in the output to -- output at least one encoded ASCII character, but the input contains an -- invalid or unrepresentable sequence InvalidSequence :: CodingProgress -- | The Latin1 (ISO8859-1) encoding. This encoding maps bytes directly to -- the first 256 Unicode code points, and is thus not a complete Unicode -- encoding. An attempt to write a character greater than '\255' to a -- Handle using the latin1 encoding will result in an -- error. latin1 :: TextEncoding latin1_encode :: CharBuffer -> Buffer Word8 -> IO (CharBuffer, Buffer Word8) latin1_decode :: Buffer Word8 -> CharBuffer -> IO (Buffer Word8, CharBuffer) -- | The UTF-8 Unicode encoding utf8 :: TextEncoding -- | The UTF-8 Unicode encoding, with a byte-order-mark (BOM; the byte -- sequence 0xEF 0xBB 0xBF). This encoding behaves like utf8, -- except that on input, the BOM sequence is ignored at the beginning of -- the stream, and on output, the BOM sequence is prepended. -- -- The byte-order-mark is strictly unnecessary in UTF-8, but is sometimes -- used to identify the encoding of a file. utf8_bom :: TextEncoding -- | The UTF-16 Unicode encoding (a byte-order-mark should be used to -- indicate endianness). utf16 :: TextEncoding -- | The UTF-16 Unicode encoding (litte-endian) utf16le :: TextEncoding -- | The UTF-16 Unicode encoding (big-endian) utf16be :: TextEncoding -- | The UTF-32 Unicode encoding (a byte-order-mark should be used to -- indicate endianness). utf32 :: TextEncoding -- | The UTF-32 Unicode encoding (litte-endian) utf32le :: TextEncoding -- | The UTF-32 Unicode encoding (big-endian) utf32be :: TextEncoding initLocaleEncoding :: TextEncoding -- | The Unicode encoding of the current locale getLocaleEncoding :: IO TextEncoding -- | The Unicode encoding of the current locale, but allowing arbitrary -- undecodable bytes to be round-tripped through it. -- -- This TextEncoding is used to decode and encode command line -- arguments and environment variables on non-Windows platforms. -- -- On Windows, this encoding *should not* be used if possible because the -- use of code pages is deprecated: Strings should be retrieved via the -- wide W-family of UTF-16 APIs instead getFileSystemEncoding :: IO TextEncoding -- | The Unicode encoding of the current locale, but where undecodable -- bytes are replaced with their closest visual match. Used for the -- CString marshalling functions in Foreign.C.String getForeignEncoding :: IO TextEncoding setLocaleEncoding :: TextEncoding -> IO () setFileSystemEncoding :: TextEncoding -> IO () setForeignEncoding :: TextEncoding -> IO () -- | An encoding in which Unicode code points are translated to bytes by -- taking the code point modulo 256. When decoding, bytes are translated -- directly into the equivalent code point. -- -- This encoding never fails in either direction. However, encoding -- discards information, so encode followed by decode is not the -- identity. char8 :: TextEncoding -- | Look up the named Unicode encoding. May fail with -- --
UTF-8
-- ... 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. forkIOWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | Like forkIO, but lets you specify on which processor the thread -- should run. Unlike a forkIO thread, a thread created by -- forkOn will stay on the same processor for its entire lifetime -- (forkIO threads can migrate between processors 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 perforamnce in some cases - -- experimentation is recommended). forkOn :: Int -> IO () -> IO ThreadId -- | This function is deprecated; use forkOn instead forkOnIO :: Int -> IO () -> IO ThreadId -- | This function is deprecated; use forkOnWIthUnmask instead forkOnIOUnmasked :: Int -> IO () -> IO ThreadId -- | Like forkIOWithUnmask, but the child thread is pinned to the -- given CPU, as with forkOn. forkOnWithUnmask :: Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | the value passed to the +RTS -N flag. This is the number of -- Haskell threads that can run truly simultaneously at any given time, -- and is typically set to the number of physical processor cores on the -- machine. -- -- Strictly speaking it is better to use getNumCapabilities, -- because the number of capabilities might vary at runtime. numCapabilities :: Int -- | Returns the number of Haskell threads that can run truly -- simultaneously (on separate physical processors) at any given time. -- The number passed to forkOn is interpreted modulo this value. -- -- An implementation in which Haskell threads are mapped directly to OS -- threads might return the number of physical processor cores in the -- machine, and forkOn would be implemented using the OS's -- affinity facilities. An implementation that schedules Haskell threads -- onto a smaller number of OS threads (like GHC) would return the number -- of such OS threads that can be running simultaneously. -- -- GHC notes: this returns the number passed as the argument to the -- +RTS -N flag. In current implementations, the value is fixed -- when the program starts and never changes, but it is possible that in -- the future the number of capabilities might vary at runtime. getNumCapabilities :: IO Int -- | Set the number of Haskell threads that can run truly simultaneously -- (on separate physical processors) at any given time. -- -- GHC notes: in the current implementation, the value may only be -- increased, not decreased, by calling setNumCapabilities. -- The initial value is given by the +RTS -N flag, and the -- current value may be obtained using getNumCapabilities. setNumCapabilities :: Int -> IO () getNumProcessors :: IO Int -- | Returns the number of sparks currently in the local spark pool numSparks :: IO Int childHandler :: SomeException -> IO () -- | Returns the ThreadId of the calling thread (GHC only). myThreadId :: IO ThreadId -- | killThread raises the ThreadKilled exception in the -- given thread (GHC only). -- --
-- killThread tid = throwTo tid ThreadKilled --killThread :: ThreadId -> IO () -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. This is a useful property to -- know when dealing with race conditions: eg. if there are two threads -- that can kill each other, it is guaranteed that only one of the -- threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () par :: a -> b -> b pseq :: a -> b -> b -- | Internal function used by the RTS to run sparks. runSparks :: IO () -- | The yield action allows (forces, in a co-operative multitasking -- implementation) a context-switch to any other currently runnable -- threads (if any), and is occasionally useful when implementing -- concurrency abstractions. yield :: IO () -- | labelThread stores a string as identifier for this thread if -- you built a RTS with debugging support. This identifier will be used -- in the debugging output to make distinction of different threads -- easier (otherwise you only have the thread state object's address in -- the heap). -- -- Other applications like the graphical Concurrent Haskell Debugger -- (http://www.informatik.uni-kiel.de/~fhu/chd/) may choose to -- overload labelThread for their purposes as well. labelThread :: ThreadId -> String -> IO () -- | The current status of a thread data ThreadStatus -- | the thread is currently runnable or running ThreadRunning :: ThreadStatus -- | the thread has finished ThreadFinished :: ThreadStatus -- | the thread is blocked on some resource ThreadBlocked :: BlockReason -> ThreadStatus -- | the thread received an uncaught exception ThreadDied :: ThreadStatus data BlockReason -- | blocked on on MVar BlockedOnMVar :: BlockReason -- | blocked on a computation in progress by another thread BlockedOnBlackHole :: BlockReason -- | blocked in throwTo BlockedOnException :: BlockReason -- | blocked in retry in an STM transaction BlockedOnSTM :: BlockReason -- | currently in a foreign call BlockedOnForeignCall :: BlockReason -- | blocked on some other resource. Without -threaded, I/O and -- threadDelay show up as BlockedOnOther, with -- -threaded they show up as BlockedOnMVar. BlockedOnOther :: BlockReason threadStatus :: ThreadId -> IO ThreadStatus -- | returns the number of the capability on which the thread is currently -- running, and a boolean indicating whether the thread is locked to that -- capability or not. A thread is locked to a capability if it was -- created with forkOn. threadCapability :: ThreadId -> IO (Int, Bool) -- | Suspends the current thread for a given number of microseconds (GHC -- only). -- -- There is no guarantee that the thread will be rescheduled promptly -- when the delay has expired, but the thread will never continue to run -- earlier than specified. threadDelay :: Int -> IO () -- | Set the value of returned TVar to True after a given number of -- microseconds. The caveats associated with threadDelay also apply. registerDelay :: Int -> IO (TVar Bool) -- | Block the current thread until data is available to read on the given -- file descriptor (GHC only). -- -- This will throw an IOError if the file descriptor was closed -- while this thread was blocked. To safely close a file descriptor that -- has been used with threadWaitRead, use closeFdWith. threadWaitRead :: Fd -> IO () -- | Block the current thread until data can be written to the given file -- descriptor (GHC only). -- -- This will throw an IOError if the file descriptor was closed -- while this thread was blocked. To safely close a file descriptor that -- has been used with threadWaitWrite, use closeFdWith. threadWaitWrite :: Fd -> IO () -- | Close a file descriptor in a concurrency-safe way (GHC only). If you -- are using threadWaitRead or threadWaitWrite to perform -- blocking I/O, you must use this function to close file -- descriptors, or blocked threads may not be woken. -- -- Any threads that are blocked on the file descriptor via -- threadWaitRead or threadWaitWrite will be unblocked by -- having IO exceptions thrown. closeFdWith :: (Fd -> IO ()) -> Fd -> IO () -- | A monad supporting atomic memory transactions. newtype STM a STM :: (State# RealWorld -> (# State# RealWorld, a #)) -> STM a -- | Perform a series of STM actions atomically. -- -- You cannot use atomically inside an unsafePerformIO or -- unsafeInterleaveIO. Any attempt to do so will result in a -- runtime error. (Reason: allowing this would effectively allow a -- transaction inside a transaction, depending on exactly when the thunk -- is evaluated.) -- -- However, see newTVarIO, which can be called inside -- unsafePerformIO, and which allows top-level TVars to be -- allocated. atomically :: STM a -> IO a -- | Retry execution of the current memory transaction because it has seen -- values in TVars which mean that it should not continue (e.g. the TVars -- represent a shared buffer that is now empty). The implementation may -- block the thread until one of the TVars that it has read from has been -- udpated. (GHC only) retry :: STM a -- | Compose two alternative STM actions (GHC only). If the first action -- completes without retrying then it forms the result of the orElse. -- Otherwise, if the first action retries, then the second action is -- tried in its place. If both actions retry then the orElse as a whole -- retries. orElse :: STM a -> STM a -> STM a -- | A variant of throw that can only be used within the STM -- monad. -- -- Throwing an exception in STM aborts the transaction and -- propagates the exception. -- -- Although throwSTM has a type that is an instance of the type of -- throw, the two functions are subtly different: -- --
-- throw e `seq` x ===> throw e -- throwSTM e `seq` x ===> x ---- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwSTM will only cause -- an exception to be raised when it is used within the STM monad. -- The throwSTM variant should be used in preference to -- throw to raise an exception within the STM monad because -- it guarantees ordering with respect to other STM operations, -- whereas throw does not. throwSTM :: Exception e => e -> STM a -- | Exception handling within STM actions. catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a -- | alwaysSucceeds adds a new invariant that must be true when passed to -- alwaysSucceeds, at the end of the current transaction, and at the end -- of every subsequent transaction. If it fails at any of those points -- then the transaction violating it is aborted and the exception raised -- by the invariant is propagated. alwaysSucceeds :: STM a -> STM () -- | always is a variant of alwaysSucceeds in which the invariant is -- expressed as an STM Bool action that must return True. Returning False -- or raising an exception are both treated as invariant failures. always :: STM Bool -> STM () -- | Shared memory locations that support atomic memory transactions. data TVar a TVar :: (TVar# RealWorld a) -> TVar a -- | Create a new TVar holding a value supplied newTVar :: a -> STM (TVar a) -- | IO version of newTVar. This is useful for creating -- top-level TVars using unsafePerformIO, because using -- atomically inside unsafePerformIO isn't possible. newTVarIO :: a -> IO (TVar a) -- | Return the current value stored in a TVar readTVar :: TVar a -> STM a -- | Return the current value stored in a TVar. This is equivalent to -- --
-- readTVarIO = atomically . readTVar ---- -- but works much faster, because it doesn't perform a complete -- transaction, it just reads the current value of the TVar. readTVarIO :: TVar a -> IO a -- | Write the supplied value into a TVar writeTVar :: TVar a -> a -> STM () -- | Unsafely performs IO in the STM monad. Beware: this is a highly -- dangerous thing to do. -- --
-- do h <- openFile "mystdout" WriteMode -- hDuplicateTo h stdout --hDuplicateTo :: Handle -> Handle -> IO () -- | Computation hClose hdl makes handle hdl -- closed. Before the computation finishes, if hdl is writable -- its buffer is flushed as for hFlush. Performing hClose -- on a handle that has already been closed has no effect; doing so is -- not an error. All other operations on a closed handle will fail. If -- hClose fails for any reason, any further operations (apart from -- hClose) on the handle will still fail as if hdl had -- been successfully closed. hClose :: Handle -> IO () hClose_help :: Handle__ -> IO (Handle__, Maybe SomeException) type HandlePosition = Integer data HandlePosn HandlePosn :: Handle -> HandlePosition -> HandlePosn -- | Computation hGetPosn hdl returns the current I/O -- position of hdl as a value of the abstract type -- HandlePosn. hGetPosn :: Handle -> IO HandlePosn -- | If a call to hGetPosn hdl returns a position -- p, then computation hSetPosn p sets the -- position of hdl to the position it held at the time of the -- call to hGetPosn. -- -- This operation may fail with: -- --
-- noNewlineTranslation = NewlineMode { inputNL = LF, outputNL = LF } --noNewlineTranslation :: NewlineMode -- | Map '\r\n' into '\n' on input, and '\n' to the native newline -- represetnation on output. This mode can be used on any platform, and -- works with text files using any newline convention. The downside is -- that readFile >>= writeFile might yield a different -- file. -- --
-- universalNewlineMode = NewlineMode { inputNL = CRLF, -- outputNL = nativeNewline } --universalNewlineMode :: NewlineMode -- | Use the native newline representation on both input and output -- --
-- nativeNewlineMode = NewlineMode { inputNL = nativeNewline -- outputNL = nativeNewline } --nativeNewlineMode :: NewlineMode -- | hShow is in the IO monad, and gives more comprehensive -- output than the (pure) instance of Show for Handle. hShow :: Handle -> IO String -- | Computation hWaitForInput hdl t waits until input is -- available on handle hdl. It returns True as soon as -- input is available on hdl, or False if no input is -- available within t milliseconds. Note that -- hWaitForInput waits until one or more full characters -- are available, which means that it needs to do decoding, and hence may -- fail with a decoding error. -- -- If t is less than zero, then hWaitForInput waits -- indefinitely. -- -- This operation may fail with: -- --
-- main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]]) --appendFile :: FilePath -> String -> IO () -- | For a handle hdl which attached to a physical file, -- hFileSize hdl returns the size of that file in 8-bit -- bytes. hFileSize :: Handle -> IO Integer -- | hSetFileSize hdl size truncates the physical -- file with handle hdl to size bytes. hSetFileSize :: Handle -> Integer -> IO () -- | For a readable handle hdl, hIsEOF hdl returns -- True if no further input can be taken from hdl or for -- a physical file, if the current I/O position is equal to the length of -- the file. Otherwise, it returns False. -- -- NOTE: hIsEOF may block, because it has to attempt to read from -- the stream to determine whether there is any more data to be read. hIsEOF :: Handle -> IO Bool -- | The computation isEOF is identical to hIsEOF, except -- that it works only on stdin. isEOF :: IO Bool -- | Three kinds of buffering are supported: line-buffering, -- block-buffering or no-buffering. These modes have the following -- effects. For output, items are written out, or flushed, from -- the internal buffer according to the buffer mode: -- --
-- main = print ([(n, 2^n) | n <- [0..19]]) --print :: Show a => a -> IO () -- | Read a character from the standard input device (same as -- hGetChar stdin). getChar :: IO Char -- | Read a line from the standard input device (same as hGetLine -- stdin). getLine :: IO String -- | The getContents operation returns all user input as a single -- string, which is read lazily as it is needed (same as -- hGetContents stdin). getContents :: IO String -- | The readIO function is similar to read except that it -- signals parse failure to the IO monad instead of terminating -- the program. readIO :: Read a => String -> IO a -- | The readLn function combines getLine and readIO. readLn :: Read a => IO a -- | withBinaryFile name mode act opens a file using -- openBinaryFile and passes the resulting handle to the -- computation act. The handle will be closed on exit from -- withBinaryFile, whether by normal termination or by raising an -- exception. withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r -- | Like openFile, but open the file in binary mode. On Windows, -- reading a file in text mode (which is the default) will translate CRLF -- to LF, and writing will translate LF to CRLF. This is usually what you -- want with text files. With binary files this is undesirable; also, as -- usual under Microsoft operating systems, text mode treats control-Z as -- EOF. Binary mode turns off all special treatment of end-of-line and -- end-of-file characters. (See also hSetBinaryMode.) openBinaryFile :: FilePath -> IOMode -> IO Handle -- | Select binary mode (True) or text mode (False) on a open -- handle. (See also openBinaryFile.) -- -- This has the same effect as calling hSetEncoding with -- char8, together with hSetNewlineMode with -- noNewlineTranslation. hSetBinaryMode :: Handle -> Bool -> IO () -- | hPutBuf hdl buf count writes count 8-bit -- bytes from the buffer buf to the handle hdl. It -- returns (). -- -- hPutBuf ignores any text encoding that applies to the -- Handle, writing the bytes directly to the underlying file or -- device. -- -- hPutBuf ignores the prevailing TextEncoding and -- NewlineMode on the Handle, and writes bytes directly. -- -- This operation may fail with: -- --
UTF-8
-- noNewlineTranslation = NewlineMode { inputNL = LF, outputNL = LF } --noNewlineTranslation :: NewlineMode -- | Map '\r\n' into '\n' on input, and '\n' to the native newline -- represetnation on output. This mode can be used on any platform, and -- works with text files using any newline convention. The downside is -- that readFile >>= writeFile might yield a different -- file. -- --
-- universalNewlineMode = NewlineMode { inputNL = CRLF, -- outputNL = nativeNewline } --universalNewlineMode :: NewlineMode -- | Use the native newline representation on both input and output -- --
-- nativeNewlineMode = NewlineMode { inputNL = nativeNewline -- outputNL = nativeNewline } --nativeNewlineMode :: NewlineMode -- | This module provides support for raising and catching both built-in -- and user-defined exceptions. -- -- In addition to exceptions thrown by IO operations, exceptions -- may be thrown by pure code (imprecise exceptions) or by external -- events (asynchronous exceptions), but may only be caught in the -- IO monad. For more details, see: -- --
-- throw e `seq` x ===> throw e -- throwIO e `seq` x ===> x ---- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwIO will only cause -- an exception to be raised when it is used within the IO monad. -- The throwIO variant should be used in preference to -- throw to raise an exception within the IO monad because -- it guarantees ordering with respect to other IO operations, -- whereas throw does not. throwIO :: Exception e => e -> IO a -- | Throw an exception. Exceptions may be thrown from purely functional -- code, but may only be caught within the IO monad. throw :: Exception e => e -> a -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. This is a useful property to -- know when dealing with race conditions: eg. if there are two threads -- that can kill each other, it is guaranteed that only one of the -- threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () -- | This is the simplest of the exception-catching functions. It takes a -- single argument, runs it, and if an exception is raised the "handler" -- is executed, with the value of the exception passed as an argument. -- Otherwise, the result is returned as normal. For example: -- --
-- catch (openFile f ReadMode) -- (\e -> hPutStr stderr ("Couldn't open "++f++": " ++ show e)) ---- -- For catching exceptions in pure (non-IO) expressions, see the -- function evaluate. -- -- Note that due to Haskell's unspecified evaluation order, an expression -- may return one of several possible exceptions: consider the expression -- error "urk" + 1 `div` 0. Does catch execute the -- handler passing ErrorCall "urk", or ArithError -- DivideByZero? -- -- The answer is "either": catch makes a non-deterministic choice -- about which exception to catch. If you call it again, you might get a -- different exception back. This is ok, because catch is an -- IO computation. -- -- Note that catch catches all types of exceptions, and is -- generally used for "cleaning up" before passing on the exception using -- throwIO. It is not good practice to discard the exception and -- continue, without first checking the type of the exception (it might -- be a ThreadKilled, for example). In this case it is usually -- better to use catchJust and select the kinds of exceptions to -- catch. -- -- Also note that the Prelude also exports a function called -- catch with a similar type to catch, except that the -- Prelude version only catches the IO and user families of -- exceptions (as required by Haskell 98). -- -- We recommend either hiding the Prelude version of catch -- when importing Control.OldException: -- --
-- import Prelude hiding (catch) ---- -- or importing Control.OldException qualified, to avoid -- name-clashes: -- --
-- import qualified Control.OldException as C ---- -- and then using C.catch catch :: IO a -> (Exception -> IO a) -> IO a -- | The function catchJust is like catch, but it takes an -- extra argument which is an exception predicate, a function -- which selects which type of exceptions we're interested in. There are -- some predefined exception predicates for useful subsets of exceptions: -- ioErrors, arithExceptions, and so on. For example, to -- catch just calls to the error function, we could use -- --
-- result <- catchJust errorCalls thing_to_try handler ---- -- Any other exceptions which are not matched by the predicate are -- re-raised, and may be caught by an enclosing catch or -- catchJust. catchJust :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a -- | A version of catch with the arguments swapped around; useful in -- situations where the code for the handler is shorter. For example: -- --
-- do handle (\e -> exitWith (ExitFailure 1)) $ -- ... --handle :: (Exception -> IO a) -> IO a -> IO a -- | A version of catchJust with the arguments swapped around (see -- handle). handleJust :: (Exception -> Maybe b) -> (b -> IO a) -> IO a -> IO a -- | Similar to catch, but returns an Either result which is -- (Right a) if no exception was raised, or -- (Left e) if an exception was raised and its value is -- e. -- --
-- try a = catch (Right `liftM` a) (return . Left) ---- -- Note: as with catch, it is only polite to use this variant if -- you intend to re-throw the exception after performing whatever cleanup -- is needed. Otherwise, tryJust is generally considered to be -- better. -- -- Also note that System.IO.Error also exports a function called -- try with a similar type to try, except that it catches -- only the IO and user families of exceptions (as required by the -- Haskell 98 IO module). try :: IO a -> IO (Either Exception a) -- | A variant of try that takes an exception predicate to select -- which exceptions are caught (c.f. catchJust). If the exception -- does not match the predicate, it is re-thrown. tryJust :: (Exception -> Maybe b) -> IO a -> IO (Either b a) -- | Forces its argument to be evaluated to weak head normal form when the -- resultant IO action is executed. It can be used to order -- evaluation with respect to other IO operations; its semantics -- are given by -- --
-- evaluate x `seq` y ==> y -- evaluate x `catch` f ==> (return $! x) `catch` f -- evaluate x >>= f ==> (return $! x) >>= f ---- -- Note: the first equation implies that (evaluate x) is -- not the same as (return $! x). A correct definition is -- --
-- evaluate x = (return $! x) >>= return --evaluate :: a -> IO a -- | This function maps one exception into another as proposed in the paper -- "A semantics for imprecise exceptions". mapException :: (Exception -> Exception) -> a -> a ioErrors :: Exception -> Maybe IOError arithExceptions :: Exception -> Maybe ArithException errorCalls :: Exception -> Maybe String dynExceptions :: Exception -> Maybe Dynamic assertions :: Exception -> Maybe String asyncExceptions :: Exception -> Maybe AsyncException userErrors :: Exception -> Maybe String -- | Raise any value as an exception, provided it is in the Typeable -- class. throwDyn :: Typeable exception => exception -> b -- | A variant of throwDyn that throws the dynamic exception to an -- arbitrary thread (GHC only: c.f. throwTo). throwDynTo :: Typeable exception => ThreadId -> exception -> IO () -- | Catch dynamic exceptions of the required type. All other exceptions -- are re-thrown, including dynamic exceptions of the wrong type. -- -- When using dynamic exceptions it is advisable to define a new datatype -- to use for your exception type, to avoid possible clashes with dynamic -- exceptions used in other libraries. catchDyn :: Typeable exception => IO a -> (exception -> IO a) -> IO a -- | Note: this function is deprecated, please use mask instead. -- -- Applying block to a computation will execute that computation -- with asynchronous exceptions blocked. That is, any thread which -- attempts to raise an exception in the current thread with -- throwTo will be blocked until asynchronous exceptions are -- unblocked again. There's no need to worry about re-enabling -- asynchronous exceptions; that is done automatically on exiting the -- scope of block. -- -- Threads created by forkIO inherit the blocked state from the -- parent; that is, to start a thread in blocked mode, use block $ -- forkIO .... This is particularly useful if you need to establish -- an exception handler in the forked thread before any asynchronous -- exceptions are received. block :: IO a -> IO a -- | Note: this function is deprecated, please use mask instead. -- -- To re-enable asynchronous exceptions inside the scope of block, -- unblock can be used. It scopes in exactly the same way, so on -- exit from unblock asynchronous exception delivery will be -- disabled again. unblock :: IO a -> IO a -- | If the first argument evaluates to True, then the result is the -- second argument. Otherwise an AssertionFailed exception is -- raised, containing a String with the source file and line -- number of the call to assert. -- -- Assertions can normally be turned on or off with a compiler flag (for -- GHC, assertions are normally on unless optimisation is turned on with -- -O or the -fignore-asserts option is given). When -- assertions are turned off, the first argument to assert is -- ignored, and the second argument is returned as the result. assert :: Bool -> a -> a -- | When you want to acquire a resource, do some work with it, and then -- release the resource, it is a good idea to use bracket, because -- bracket will install the necessary exception handler to release -- the resource in the event that an exception is raised during the -- computation. If an exception is raised, then bracket will -- re-raise the exception (after performing the release). -- -- A common example is opening a file: -- --
-- bracket -- (openFile "filename" ReadMode) -- (hClose) -- (\handle -> do { ... }) ---- -- The arguments to bracket are in this order so that we can -- partially apply it, e.g.: -- --
-- withFile name mode = bracket (openFile name mode) hClose --bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c -- | A variant of bracket where the return value from the first -- computation is not required. bracket_ :: IO a -> IO b -> IO c -> IO c -- | Like bracket, but only performs the final action if there was an -- exception raised by the in-between computation. bracketOnError :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c -- | A specialised variant of bracket with just a computation to run -- afterward. finally :: IO a -> IO b -> IO a setUncaughtExceptionHandler :: (Exception -> IO ()) -> IO () getUncaughtExceptionHandler :: IO (Exception -> IO ()) instance Typeable Exception instance Eq Exception instance Show Exception instance Exception Exception -- | The Prelude: a standard module imported by default into all Haskell -- modules. For more documentation, see the Haskell 98 Report -- http://www.haskell.org/onlinereport/. module Prelude data Bool :: * False :: Bool True :: Bool -- | Boolean "and" (&&) :: Bool -> Bool -> Bool -- | Boolean "or" (||) :: Bool -> Bool -> Bool -- | Boolean "not" not :: Bool -> Bool -- | otherwise is defined as the value True. It helps to make -- guards more readable. eg. -- --
-- f x | x < 0 = ... -- | otherwise = ... --otherwise :: Bool -- | The Maybe type encapsulates an optional value. A value of type -- Maybe a either contains a value of type a -- (represented as Just a), or it is empty (represented -- as Nothing). Using Maybe is a good way to deal with -- errors or exceptional cases without resorting to drastic measures such -- as error. -- -- The Maybe type is also a monad. It is a simple kind of error -- monad, where all errors are represented by Nothing. A richer -- error monad can be built using the Either type. data Maybe a Nothing :: Maybe a Just :: a -> Maybe a -- | The maybe function takes a default value, a function, and a -- Maybe value. If the Maybe value is Nothing, the -- function returns the default value. Otherwise, it applies the function -- to the value inside the Just and returns the result. maybe :: b -> (a -> b) -> Maybe a -> b -- | The Either type represents values with two possibilities: a -- value of type Either a b is either Left -- a or Right b. -- -- The Either type is sometimes used to represent a value which is -- either correct or an error; by convention, the Left constructor -- is used to hold an error value and the Right constructor is -- used to hold a correct value (mnemonic: "right" also means "correct"). data Either a b Left :: a -> Either a b Right :: b -> Either a b -- | Case analysis for the Either type. If the value is -- Left a, apply the first function to a; if it -- is Right b, apply the second function to b. either :: (a -> c) -> (b -> c) -> Either a b -> c data Ordering :: * LT :: Ordering EQ :: Ordering GT :: Ordering -- | The character type Char is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) characters (see -- http://www.unicode.org/ for details). This set extends the ISO -- 8859-1 (Latin-1) character set (the first 256 characters), which is -- itself an extension of the ASCII character set (the first 128 -- characters). A character literal in Haskell has type Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char :: * -- | A String is a list of characters. String constants in Haskell -- are values of type String. type String = [Char] -- | Extract the first component of a pair. fst :: (a, b) -> a -- | Extract the second component of a pair. snd :: (a, b) -> b -- | curry converts an uncurried function to a curried function. curry :: ((a, b) -> c) -> a -> b -> c -- | uncurry converts a curried function to a function on pairs. uncurry :: (a -> b -> c) -> ((a, b) -> c) -- | The Eq class defines equality (==) and inequality -- (/=). All the basic datatypes exported by the Prelude -- are instances of Eq, and Eq may be derived for any -- datatype whose constituents are also instances of Eq. -- -- Minimal complete definition: either == or /=. class Eq a (==) :: Eq a => a -> a -> Bool (/=) :: Eq a => a -> a -> Bool -- | The Ord class is used for totally ordered datatypes. -- -- Instances of Ord can be derived for any user-defined datatype -- whose constituent types are in Ord. The declared order of the -- constructors in the data declaration determines the ordering in -- derived Ord instances. The Ordering datatype allows a -- single comparison to determine the precise ordering of two objects. -- -- Minimal complete definition: either compare or <=. -- Using compare can be more efficient for complex types. class Eq a => Ord a compare :: Ord a => a -> a -> Ordering (<) :: Ord a => a -> a -> Bool (>=) :: Ord a => a -> a -> Bool (>) :: Ord a => a -> a -> Bool (<=) :: Ord a => a -> a -> Bool max :: Ord a => a -> a -> a min :: Ord a => a -> a -> a -- | Class Enum defines operations on sequentially ordered types. -- -- The enumFrom... methods are used in Haskell's translation of -- arithmetic sequences. -- -- Instances of Enum may be derived for any enumeration type -- (types whose constructors have no fields). The nullary constructors -- are assumed to be numbered left-to-right by fromEnum from -- 0 through n-1. See Chapter 10 of the Haskell -- Report for more details. -- -- For any type that is an instance of class Bounded as well as -- Enum, the following should hold: -- --
-- enumFrom x = enumFromTo x maxBound -- enumFromThen x y = enumFromThenTo x y bound -- where -- bound | fromEnum y >= fromEnum x = maxBound -- | otherwise = minBound --class Enum a where succ = toEnum . (`plusInt` oneInt) . fromEnum pred = toEnum . (`minusInt` oneInt) . fromEnum enumFrom x = map toEnum [fromEnum x .. ] enumFromThen x y = map toEnum [fromEnum x, fromEnum y .. ] enumFromTo x y = map toEnum [fromEnum x .. fromEnum y] enumFromThenTo x1 x2 y = map toEnum [fromEnum x1, fromEnum x2 .. fromEnum y] succ :: Enum a => a -> a pred :: Enum a => a -> a toEnum :: Enum a => Int -> a fromEnum :: Enum a => a -> Int enumFrom :: Enum a => a -> [a] enumFromThen :: Enum a => a -> a -> [a] enumFromTo :: Enum a => a -> a -> [a] enumFromThenTo :: Enum a => a -> a -> a -> [a] -- | The Bounded class is used to name the upper and lower limits of -- a type. Ord is not a superclass of Bounded since types -- that are not totally ordered may also have upper and lower bounds. -- -- The Bounded class may be derived for any enumeration type; -- minBound is the first constructor listed in the data -- declaration and maxBound is the last. Bounded may also -- be derived for single-constructor datatypes whose constituent types -- are in Bounded. class Bounded a minBound, maxBound :: Bounded a => a -- | A fixed-precision integer type with at least the range [-2^29 .. -- 2^29-1]. The exact range for a given implementation can be -- determined by using minBound and maxBound from the -- Bounded class. data Int :: * -- | Arbitrary-precision integers. data Integer :: * -- | Single-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- single-precision type. data Float :: * -- | Double-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- double-precision type. data Double :: * -- | Arbitrary-precision rational numbers, represented as a ratio of two -- Integer values. A rational number may be constructed using the -- % operator. type Rational = Ratio Integer -- | Basic numeric class. -- -- Minimal complete definition: all except negate or (-) class Num a where x - y = x + negate y negate x = 0 - x (+, *, -) :: Num a => a -> a -> a negate :: Num a => a -> a abs :: Num a => a -> a signum :: Num a => a -> a fromInteger :: Num a => Integer -> a class (Num a, Ord a) => Real a toRational :: Real a => a -> Rational -- | Integral numbers, supporting integer division. -- -- Minimal complete definition: quotRem and toInteger class (Real a, Enum a) => Integral a where n quot d = q where (q, _) = quotRem n d n rem d = r where (_, r) = quotRem n d n div d = q where (q, _) = divMod n d n mod d = r where (_, r) = divMod n d divMod n d = if signum r == negate (signum d) then (q - 1, r + d) else qr where qr@(q, r) = quotRem n d quot :: Integral a => a -> a -> a rem :: Integral a => a -> a -> a div :: Integral a => a -> a -> a mod :: Integral a => a -> a -> a quotRem :: Integral a => a -> a -> (a, a) divMod :: Integral a => a -> a -> (a, a) toInteger :: Integral a => a -> Integer -- | Fractional numbers, supporting real division. -- -- Minimal complete definition: fromRational and (recip or -- (/)) class Num a => Fractional a where recip x = 1 / x x / y = x * recip y (/) :: Fractional a => a -> a -> a recip :: Fractional a => a -> a fromRational :: Fractional a => Rational -> a -- | Trigonometric and hyperbolic functions and related functions. -- -- Minimal complete definition: pi, exp, log, -- sin, cos, sinh, cosh, asin, -- acos, atan, asinh, acosh and atanh class Fractional a => Floating a where x ** y = exp (log x * y) logBase x y = log y / log x sqrt x = x ** 0.5 tan x = sin x / cos x tanh x = sinh x / cosh x pi :: Floating a => a exp, sqrt, log :: Floating a => a -> a (**, logBase) :: Floating a => a -> a -> a sin, tan, cos :: Floating a => a -> a asin, atan, acos :: Floating a => a -> a sinh, tanh, cosh :: Floating a => a -> a asinh, atanh, acosh :: Floating a => a -> a -- | Extracting components of fractions. -- -- Minimal complete definition: properFraction class (Real a, Fractional a) => RealFrac a where truncate x = m where (m, _) = properFraction x round x = let (n, r) = properFraction x m = if r < 0 then n - 1 else n + 1 in case signum (abs r - 0.5) of { -1 -> n 0 -> if even n then n else m 1 -> m _ -> error "round default defn: Bad value" } ceiling x = if r > 0 then n + 1 else n where (n, r) = properFraction x floor x = if r < 0 then n - 1 else n where (n, r) = properFraction x properFraction :: (RealFrac a, Integral b) => a -> (b, a) truncate :: (RealFrac a, Integral b) => a -> b round :: (RealFrac a, Integral b) => a -> b ceiling :: (RealFrac a, Integral b) => a -> b floor :: (RealFrac a, Integral b) => a -> b -- | Efficient, machine-independent access to the components of a -- floating-point number. -- -- Minimal complete definition: all except exponent, -- significand, scaleFloat and atan2 class (RealFrac a, Floating a) => RealFloat a where exponent x = if m == 0 then 0 else n + floatDigits x where (m, n) = decodeFloat x significand x = encodeFloat m (negate (floatDigits x)) where (m, _) = decodeFloat x scaleFloat 0 x = x scaleFloat k x | isFix = x | otherwise = encodeFloat m (n + clamp b k) where (m, n) = decodeFloat x (l, h) = floatRange x d = floatDigits x b = h - l + 4 * d isFix = x == 0 || isNaN x || isInfinite x atan2 y x | x > 0 = atan (y / x) | x == 0 && y > 0 = pi / 2 | x < 0 && y > 0 = pi + atan (y / x) | (x <= 0 && y < 0) || (x < 0 && isNegativeZero y) || (isNegativeZero x && isNegativeZero y) = - atan2 (- y) x | y == 0 && (x < 0 || isNegativeZero x) = pi | x == 0 && y == 0 = y | otherwise = x + y floatRadix :: RealFloat a => a -> Integer floatDigits :: RealFloat a => a -> Int floatRange :: RealFloat a => a -> (Int, Int) decodeFloat :: RealFloat a => a -> (Integer, Int) encodeFloat :: RealFloat a => Integer -> Int -> a exponent :: RealFloat a => a -> Int significand :: RealFloat a => a -> a scaleFloat :: RealFloat a => Int -> a -> a isNaN :: RealFloat a => a -> Bool isInfinite :: RealFloat a => a -> Bool isDenormalized :: RealFloat a => a -> Bool isNegativeZero :: RealFloat a => a -> Bool isIEEE :: RealFloat a => a -> Bool atan2 :: RealFloat a => a -> a -> a -- | the same as flip (-). -- -- Because - is treated specially in the Haskell grammar, -- (- e) is not a section, but an application of -- prefix negation. However, (subtract -- exp) is equivalent to the disallowed section. subtract :: Num a => a -> a -> a even :: Integral a => a -> Bool odd :: Integral a => a -> Bool -- | gcd x y is the non-negative factor of both x -- and y of which every common factor of x and -- y is also a factor; for example gcd 4 2 = 2, -- gcd (-4) 6 = 2, gcd 0 4 = 4. -- gcd 0 0 = 0. (That is, the common divisor -- that is "greatest" in the divisibility preordering.) -- -- Note: Since for signed fixed-width integer types, abs -- minBound < 0, the result may be negative if one of the -- arguments is minBound (and necessarily is if the other -- is 0 or minBound) for such types. gcd :: Integral a => a -> a -> a -- | lcm x y is the smallest positive integer that both -- x and y divide. lcm :: Integral a => a -> a -> a -- | raise a number to a non-negative integral power (^) :: (Num a, Integral b) => a -> b -> a -- | raise a number to an integral power (^^) :: (Fractional a, Integral b) => a -> b -> a -- | general coercion from integral types fromIntegral :: (Integral a, Num b) => a -> b -- | general coercion to fractional types realToFrac :: (Real a, Fractional b) => a -> b -- | The Monad class defines the basic operations over a -- monad, a concept from a branch of mathematics known as -- category theory. From the perspective of a Haskell programmer, -- however, it is best to think of a monad as an abstract datatype -- of actions. Haskell's do expressions provide a convenient -- syntax for writing monadic expressions. -- -- Minimal complete definition: >>= and return. -- -- Instances of Monad should satisfy the following laws: -- --
-- return a >>= k == k a -- m >>= return == m -- m >>= (\x -> k x >>= h) == (m >>= k) >>= h ---- -- Instances of both Monad and Functor should additionally -- satisfy the law: -- --
-- fmap f xs == xs >>= return . f ---- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Monad m where m >> k = m >>= \ _ -> k fail s = error s (>>=) :: Monad m => m a -> (a -> m b) -> m b (>>) :: Monad m => m a -> m b -> m b return :: Monad m => a -> m a fail :: Monad m => String -> m a -- | The Functor class is used for types that can be mapped over. -- Instances of Functor should satisfy the following laws: -- --
-- fmap id == id -- fmap (f . g) == fmap f . fmap g ---- -- The instances of Functor for lists, Maybe and IO -- satisfy these laws. class Functor f where <$ = fmap . const fmap :: Functor f => (a -> b) -> f a -> f b -- | mapM f is equivalent to sequence . -- map f. mapM :: Monad m => (a -> m b) -> [a] -> m [b] -- | mapM_ f is equivalent to sequence_ . -- map f. mapM_ :: Monad m => (a -> m b) -> [a] -> m () -- | Evaluate each action in the sequence from left to right, and collect -- the results. sequence :: Monad m => [m a] -> m [a] -- | Evaluate each action in the sequence from left to right, and ignore -- the results. sequence_ :: Monad m => [m a] -> m () -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b -- | Identity function. id :: a -> a -- | Constant function. const :: a -> b -> a -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c -- | flip f takes its (first) two arguments in the reverse -- order of f. flip :: (a -> b -> c) -> b -> a -> c -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ has low, right-associative binding precedence, so it -- sometimes allows parentheses to be omitted; for example: -- --
-- f $ g $ h x = f (g (h x)) ---- -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. ($) :: (a -> b) -> a -> b -- | until p f yields the result of applying f -- until p holds. until :: (a -> Bool) -> (a -> a) -> a -> a -- | asTypeOf is a type-restricted version of const. It is -- usually used as an infix operator, and its typing forces its first -- argument (which is usually overloaded) to have the same type as the -- second. asTypeOf :: a -> a -> a -- | error stops execution and displays an error message. error :: [Char] -> a -- | A special case of error. It is expected that compilers will -- recognize this and insert error messages which are more appropriate to -- the context in which undefined appears. undefined :: a -- | Evaluates its first argument to head normal form, and then returns its -- second argument as the result. seq :: a -> b -> b -- | Strict (call-by-value) application, defined in terms of seq. ($!) :: (a -> b) -> a -> b -- | map f xs is the list obtained by applying f -- to each element of xs, i.e., -- --
-- map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] -- map f [x1, x2, ...] == [f x1, f x2, ...] --map :: (a -> b) -> [a] -> [b] -- | Append two lists, i.e., -- --
-- [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] -- [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...] ---- -- If the first list is not finite, the result is the first list. (++) :: [a] -> [a] -> [a] -- | filter, applied to a predicate and a list, returns the list of -- those elements that satisfy the predicate; i.e., -- --
-- filter p xs = [ x | x <- xs, p x] --filter :: (a -> Bool) -> [a] -> [a] -- | Extract the first element of a list, which must be non-empty. head :: [a] -> a -- | Extract the last element of a list, which must be finite and -- non-empty. last :: [a] -> a -- | Extract the elements after the head of a list, which must be -- non-empty. tail :: [a] -> [a] -- | Return all the elements of a list except the last one. The list must -- be non-empty. init :: [a] -> [a] -- | Test whether a list is empty. null :: [a] -> Bool -- | O(n). length returns the length of a finite list as an -- Int. It is an instance of the more general -- genericLength, the result type of which may be any kind of -- number. length :: [a] -> Int -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. (!!) :: [a] -> Int -> a -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. reverse :: [a] -> [a] -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a list, reduces the -- list using the binary operator, from left to right: -- --
-- foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn ---- -- The list must be finite. foldl :: (a -> b -> a) -> a -> [b] -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty lists. foldl1 :: (a -> a -> a) -> [a] -> a -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a list, reduces -- the list using the binary operator, from right to left: -- --
-- foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) --foldr :: (a -> b -> b) -> b -> [a] -> b -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty lists. foldr1 :: (a -> a -> a) -> [a] -> a -- | and returns the conjunction of a Boolean list. For the result -- to be True, the list must be finite; False, however, -- results from a False value at a finite index of a finite or -- infinite list. and :: [Bool] -> Bool -- | or returns the disjunction of a Boolean list. For the result to -- be False, the list must be finite; True, however, -- results from a True value at a finite index of a finite or -- infinite list. or :: [Bool] -> Bool -- | Applied to a predicate and a list, any determines if any -- element of the list satisfies the predicate. For the result to be -- False, the list must be finite; True, however, results -- from a True value for the predicate applied to an element at a -- finite index of a finite or infinite list. any :: (a -> Bool) -> [a] -> Bool -- | Applied to a predicate and a list, all determines if all -- elements of the list satisfy the predicate. For the result to be -- True, the list must be finite; False, however, results -- from a False value for the predicate applied to an element at a -- finite index of a finite or infinite list. all :: (a -> Bool) -> [a] -> Bool -- | The sum function computes the sum of a finite list of numbers. sum :: Num a => [a] -> a -- | The product function computes the product of a finite list of -- numbers. product :: Num a => [a] -> a -- | Concatenate a list of lists. concat :: [[a]] -> [a] -- | Map a function over a list and concatenate the results. concatMap :: (a -> [b]) -> [a] -> [b] -- | maximum returns the maximum value from a list, which must be -- non-empty, finite, and of an ordered type. It is a special case of -- maximumBy, which allows the programmer to supply their own -- comparison function. maximum :: Ord a => [a] -> a -- | minimum returns the minimum value from a list, which must be -- non-empty, finite, and of an ordered type. It is a special case of -- minimumBy, which allows the programmer to supply their own -- comparison function. minimum :: Ord a => [a] -> a -- | scanl is similar to foldl, but returns a list of -- successive reduced values from the left: -- --
-- scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...] ---- -- Note that -- --
-- last (scanl f z xs) == foldl f z xs. --scanl :: (a -> b -> a) -> a -> [b] -> [a] -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
-- scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...] --scanl1 :: (a -> a -> a) -> [a] -> [a] -- | scanr is the right-to-left dual of scanl. Note that -- --
-- head (scanr f z xs) == foldr f z xs. --scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (a -> a -> a) -> [a] -> [a] -- | iterate f x returns an infinite list of repeated -- applications of f to x: -- --
-- iterate f x == [x, f x, f (f x), ...] --iterate :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. repeat :: a -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. replicate :: Int -> a -> [a] -- | cycle ties a finite list into a circular one, or equivalently, -- the infinite repetition of the original list. It is the identity on -- infinite lists. cycle :: [a] -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n > length xs: -- --
-- take 5 "Hello World!" == "Hello" -- take 3 [1,2,3,4,5] == [1,2,3] -- take 3 [1,2] == [1,2] -- take 3 [] == [] -- take (-1) [1,2] == [] -- take 0 [1,2] == [] ---- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. take :: Int -> [a] -> [a] -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n > length -- xs: -- --
-- drop 6 "Hello World!" == "World!" -- drop 3 [1,2,3,4,5] == [4,5] -- drop 3 [1,2] == [] -- drop 3 [] == [] -- drop (-1) [1,2] == [1,2] -- drop 0 [1,2] == [1,2] ---- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. drop :: Int -> [a] -> [a] -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
-- splitAt 6 "Hello World!" == ("Hello ","World!") -- splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) -- splitAt 1 [1,2,3] == ([1],[2,3]) -- splitAt 3 [1,2,3] == ([1,2,3],[]) -- splitAt 4 [1,2,3] == ([1,2,3],[]) -- splitAt 0 [1,2,3] == ([],[1,2,3]) -- splitAt (-1) [1,2,3] == ([],[1,2,3]) ---- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) -- | takeWhile, applied to a predicate p and a list -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p: -- --
-- takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] -- takeWhile (< 9) [1,2,3] == [1,2,3] -- takeWhile (< 0) [1,2,3] == [] --takeWhile :: (a -> Bool) -> [a] -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs: -- --
-- dropWhile (< 3) [1,2,3,4,5,1,2,3] == [3,4,5,1,2,3] -- dropWhile (< 9) [1,2,3] == [] -- dropWhile (< 0) [1,2,3] == [1,2,3] --dropWhile :: (a -> Bool) -> [a] -> [a] -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is longest prefix (possibly empty) -- of xs of elements that satisfy p and second element -- is the remainder of the list: -- --
-- span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) -- span (< 9) [1,2,3] == ([1,2,3],[]) -- span (< 0) [1,2,3] == ([],[1,2,3]) ---- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | break, applied to a predicate p and a list -- xs, returns a tuple where first element is longest prefix -- (possibly empty) of xs of elements that do not satisfy -- p and second element is the remainder of the list: -- --
-- break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) -- break (< 9) [1,2,3] == ([],[1,2,3]) -- break (> 9) [1,2,3] == ([1,2,3],[]) ---- -- break p is equivalent to span (not . -- p). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | elem is the list membership predicate, usually written in infix -- form, e.g., x `elem` xs. For the result to be False, -- the list must be finite; True, however, results from an element -- equal to x found at a finite index of a finite or infinite -- list. elem :: Eq a => a -> [a] -> Bool -- | notElem is the negation of elem. notElem :: Eq a => a -> [a] -> Bool -- | lookup key assocs looks up a key in an association -- list. lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | zip takes two lists and returns a list of corresponding pairs. -- If one input list is short, excess elements of the longer list are -- discarded. zip :: [a] -> [b] -> [(a, b)] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two lists to -- produce the list of corresponding sums. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | The zipWith3 function takes a function which combines three -- elements, as well as three lists and returns a list of their -- point-wise combination, analogous to zipWith. zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] -- | unzip transforms a list of pairs into a list of first -- components and a list of second components. unzip :: [(a, b)] -> ([a], [b]) -- | The unzip3 function takes a list of triples and returns three -- lists, analogous to unzip. unzip3 :: [(a, b, c)] -> ([a], [b], [c]) -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space. words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. unlines :: [String] -> String -- | unwords is an inverse operation to words. It joins words -- with separating spaces. unwords :: [String] -> String -- | The shows functions return a function that prepends the -- output String to an existing String. This allows -- constant-time concatenation of results using function composition. type ShowS = String -> String -- | Conversion of values to readable Strings. -- -- Minimal complete definition: showsPrec or show. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Show is equivalent to -- --
-- instance (Show a) => Show (Tree a) where -- -- showsPrec d (Leaf m) = showParen (d > app_prec) $ -- showString "Leaf " . showsPrec (app_prec+1) m -- where app_prec = 10 -- -- showsPrec d (u :^: v) = showParen (d > up_prec) $ -- showsPrec (up_prec+1) u . -- showString " :^: " . -- showsPrec (up_prec+1) v -- where up_prec = 5 ---- -- Note that right-associativity of :^: is ignored. For example, -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Read in Haskell 98 is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readsPrec d r = readParen (d > app_prec) -- (\r -> [(Leaf m,t) | -- ("Leaf",s) <- lex r, -- (m,t) <- readsPrec (app_prec+1) s]) r -- -- ++ readParen (d > up_prec) -- (\r -> [(u:^:v,w) | -- (u,s) <- readsPrec (up_prec+1) r, -- (":^:",t) <- lex s, -- (v,w) <- readsPrec (up_prec+1) t]) r -- -- where app_prec = 10 -- up_prec = 5 ---- -- Note that right-associativity of :^: is unused. -- -- The derived instance in GHC is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readPrec = parens $ (prec app_prec $ do -- Ident "Leaf" <- lexP -- m <- step readPrec -- return (Leaf m)) -- -- +++ (prec up_prec $ do -- u <- step readPrec -- Symbol ":^:" <- lexP -- v <- step readPrec -- return (u :^: v)) -- -- where app_prec = 10 -- up_prec = 5 -- -- readListPrec = readListPrecDefault --class Read a where readsPrec = readPrec_to_S readPrec readList = readPrec_to_S (list readPrec) 0 readPrec = readS_to_Prec readsPrec readListPrec = readS_to_Prec (\ _ -> readList) readsPrec :: Read a => Int -> ReadS a readList :: Read a => ReadS [a] -- | equivalent to readsPrec with a precedence of 0. reads :: Read a => ReadS a -- | readParen True p parses what p parses, -- but surrounded with parentheses. -- -- readParen False p parses what p -- parses, but optionally surrounded with parentheses. readParen :: Bool -> ReadS a -> ReadS a -- | The read function reads input from a string, which must be -- completely consumed by the input process. read :: Read a => String -> a -- | The lex function reads a single lexeme from the input, -- discarding initial white space, and returning the characters that -- constitute the lexeme. If the input string contains only white space, -- lex returns a single successful `lexeme' consisting of the -- empty string. (Thus lex "" = [("","")].) If there is -- no legal lexeme at the beginning of the input string, lex fails -- (i.e. returns []). -- -- This lexer is not completely faithful to the Haskell lexical syntax in -- the following respects: -- --
-- main = print ([(n, 2^n) | n <- [0..19]]) --print :: Show a => a -> IO () -- | Read a character from the standard input device (same as -- hGetChar stdin). getChar :: IO Char -- | Read a line from the standard input device (same as hGetLine -- stdin). getLine :: IO String -- | The getContents operation returns all user input as a single -- string, which is read lazily as it is needed (same as -- hGetContents stdin). getContents :: IO String -- | The interact function takes a function of type -- String->String as its argument. The entire input from the -- standard input device is passed to this function as its argument, and -- the resulting string is output on the standard output device. interact :: (String -> String) -> IO () -- | File and directory names are values of type String, whose -- precise meaning is operating system dependent. Files can be opened, -- yielding a handle which can then be used to operate on the contents of -- that file. type FilePath = String -- | The readFile function reads a file and returns the contents of -- the file as a string. The file is read lazily, on demand, as with -- getContents. readFile :: FilePath -> IO String -- | The computation writeFile file str function writes the -- string str, to the file file. writeFile :: FilePath -> String -> IO () -- | The computation appendFile file str function appends -- the string str, to the file file. -- -- Note that writeFile and appendFile write a literal -- string to a file. To write a value of any printable type, as with -- print, use the show function to convert the value to a -- string first. -- --
-- main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]]) --appendFile :: FilePath -> String -> IO () -- | The readIO function is similar to read except that it -- signals parse failure to the IO monad instead of terminating -- the program. readIO :: Read a => String -> IO a -- | The readLn function combines getLine and readIO. readLn :: Read a => IO a -- | The Haskell 98 type for exceptions in the IO monad. Any I/O -- operation may raise an IOError instead of returning a result. -- For a more general type of exception, including also those that arise -- in pure code, see Control.Exception.Exception. -- -- In Haskell 98, this is an opaque type. type IOError = IOException -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | Construct an IOError value with a string describing the error. -- The fail method of the IO instance of the Monad -- class raises a userError, thus: -- --
-- instance Monad IO where -- ... -- fail s = ioError (userError s) --userError :: String -> IOError -- | The catch function is deprecated. Please use the new exceptions -- variant, catch from Control.Exception, instead. catch :: IO a -> (IOError -> IO a) -> IO a -- | "Scrap your boilerplate" --- Generic programming in Haskell. See -- http://www.cs.vu.nl/boilerplate/. This module provides the -- Data class with its primitives for generic programming, along -- with instances for many datatypes. It corresponds to a merge between -- the previous Data.Generics.Basics and almost all of -- Data.Generics.Instances. The instances that are not present in -- this module were moved to the Data.Generics.Instances module -- in the syb package. -- -- For more information, please visit the new SYB wiki: -- http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB. module Data.Data -- | The Data class comprehends a fundamental primitive -- gfoldl for folding over constructor applications, say terms. -- This primitive can be instantiated in several ways to map over the -- immediate subterms of a term; see the gmap combinators later -- in this class. Indeed, a generic programmer does not necessarily need -- to use the ingenious gfoldl primitive but rather the intuitive -- gmap combinators. The gfoldl primitive is completed by -- means to query top-level constructors, to turn constructor -- representations into proper terms, and to list all possible datatype -- constructors. This completion allows us to serve generic programming -- scenarios like read, show, equality, term generation. -- -- The combinators gmapT, gmapQ, gmapM, etc are all -- provided with default definitions in terms of gfoldl, leaving -- open the opportunity to provide datatype-specific definitions. (The -- inclusion of the gmap combinators as members of class -- Data allows the programmer or the compiler to derive -- specialised, and maybe more efficient code per datatype. Note: -- gfoldl is more higher-order than the gmap combinators. -- This is subject to ongoing benchmarking experiments. It might turn out -- that the gmap combinators will be moved out of the class -- Data.) -- -- Conceptually, the definition of the gmap combinators in terms -- of the primitive gfoldl requires the identification of the -- gfoldl function arguments. Technically, we also need to -- identify the type constructor c for the construction of the -- result type from the folded term type. -- -- In the definition of gmapQx combinators, we use -- phantom type constructors for the c in the type of -- gfoldl because the result type of a query does not involve the -- (polymorphic) type of the term argument. In the definition of -- gmapQl we simply use the plain constant type constructor -- because gfoldl is left-associative anyway and so it is readily -- suited to fold a left-associative binary operation over the immediate -- subterms. In the definition of gmapQr, extra effort is needed. We use -- a higher-order accumulation trick to mediate between left-associative -- constructor application vs. right-associative binary operation (e.g., -- (:)). When the query is meant to compute a value of type -- r, then the result type withing generic folding is r -- -> r. So the result of folding is a function to which we -- finally pass the right unit. -- -- With the -XDeriveDataTypeable option, GHC can generate -- instances of the Data class automatically. For example, given -- the declaration -- --
-- data T a b = C1 a b | C2 deriving (Typeable, Data) ---- -- GHC will generate an instance that is equivalent to -- --
-- instance (Data a, Data b) => Data (T a b) where -- gfoldl k z (C1 a b) = z C1 `k` a `k` b -- gfoldl k z C2 = z C2 -- -- gunfold k z c = case constrIndex c of -- 1 -> k (k (z C1)) -- 2 -> z C2 -- -- toConstr (C1 _ _) = con_C1 -- toConstr C2 = con_C2 -- -- dataTypeOf _ = ty_T -- -- con_C1 = mkConstr ty_T "C1" [] Prefix -- con_C2 = mkConstr ty_T "C2" [] Prefix -- ty_T = mkDataType "Module.T" [con_C1, con_C2] ---- -- This is suitable for datatypes that are exported transparently. class Typeable a => Data a where gfoldl _ z = z dataCast1 _ = Nothing dataCast2 _ = Nothing gmapT f x0 = unID (gfoldl k ID x0) where k :: Data d => ID (d -> b) -> d -> ID b k (ID c) x = ID (c (f x)) gmapQl o r f = unCONST . gfoldl k z where k :: Data d => CONST r (d -> b) -> d -> CONST r b k c x = CONST $ (unCONST c) `o` f x z :: g -> CONST r g z _ = CONST r gmapQr o r0 f x0 = unQr (gfoldl k (const (Qr id)) x0) r0 where k :: Data d => Qr r (d -> b) -> d -> Qr r b k (Qr c) x = Qr (\ r -> c (f x `o` r)) gmapQ f = gmapQr (:) [] f gmapQi i f x = case gfoldl k z x of { Qi _ q -> fromJust q } where k :: Data d => Qi u (d -> b) -> d -> Qi u b k (Qi i' q) a = Qi (i' + 1) (if i == i' then Just (f a) else q) z :: g -> Qi q g z _ = Qi 0 Nothing gmapM f = gfoldl k return where k :: Data d => m (d -> b) -> d -> m b k c x = do { c' <- c; x' <- f x; return (c' x') } gmapMp f x = unMp (gfoldl k z x) >>= \ (x', b) -> if b then return x' else mzero where z :: g -> Mp m g z g = Mp (return (g, False)) k :: Data d => Mp m (d -> b) -> d -> Mp m b k (Mp c) y = Mp (c >>= \ (h, b) -> (f y >>= \ y' -> return (h y', True)) `mplus` return (h y, b)) gmapMo f x = unMp (gfoldl k z x) >>= \ (x', b) -> if b then return x' else mzero where z :: g -> Mp m g z g = Mp (return (g, False)) k :: Data d => Mp m (d -> b) -> d -> Mp m b k (Mp c) y = Mp (c >>= \ (h, b) -> if b then return (h y, b) else (f y >>= \ y' -> return (h y', True)) `mplus` return (h y, b)) gfoldl :: Data a => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a gunfold :: Data a => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a toConstr :: Data a => a -> Constr dataTypeOf :: Data a => a -> DataType dataCast1 :: (Data a, Typeable1 t) => (forall d. Data d => c (t d)) -> Maybe (c a) dataCast2 :: (Data a, Typeable2 t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a) gmapT :: Data a => (forall b. Data b => b -> b) -> a -> a gmapQl :: Data a => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r gmapQr :: Data a => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r gmapQ :: Data a => (forall d. Data d => d -> u) -> a -> [u] gmapQi :: Data a => Int -> (forall d. Data d => d -> u) -> a -> u gmapM :: (Data a, Monad m) => (forall d. Data d => d -> m d) -> a -> m a gmapMp :: (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a gmapMo :: (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Representation of datatypes. A package of constructor representations -- with names of type and module. data DataType -- | Constructs an algebraic datatype mkDataType :: String -> [Constr] -> DataType -- | Constructs the Int type mkIntType :: String -> DataType -- | Constructs the Float type mkFloatType :: String -> DataType -- | This function is now deprecated. Please use mkCharType instead. -- | Deprecated: Use mkCharType instead mkStringType :: String -> DataType -- | Constructs the Char type mkCharType :: String -> DataType -- | Constructs a non-representation for a non-presentable type mkNoRepType :: String -> DataType -- | Deprecated version (misnamed) -- | Deprecated: Use mkNoRepType instead mkNorepType :: String -> DataType -- | Gets the type constructor including the module dataTypeName :: DataType -> String -- | Public representation of datatypes data DataRep AlgRep :: [Constr] -> DataRep IntRep :: DataRep FloatRep :: DataRep CharRep :: DataRep NoRep :: DataRep -- | Gets the public presentation of a datatype dataTypeRep :: DataType -> DataRep -- | Look up a constructor by its representation repConstr :: DataType -> ConstrRep -> Constr -- | Test for an algebraic type isAlgType :: DataType -> Bool -- | Gets the constructors of an algebraic datatype dataTypeConstrs :: DataType -> [Constr] -- | Gets the constructor for an index (algebraic datatypes only) indexConstr :: DataType -> ConIndex -> Constr -- | Gets the maximum constructor index of an algebraic datatype maxConstrIndex :: DataType -> ConIndex -- | Test for a non-representable type isNorepType :: DataType -> Bool -- | Representation of constructors. Note that equality on constructors -- with different types may not work -- i.e. the constructors for -- False and Nothing may compare equal. data Constr -- | Unique index for datatype constructors, counting from 1 in the order -- they are given in the program text. type ConIndex = Int -- | Fixity of constructors data Fixity Prefix :: Fixity Infix :: Fixity -- | Constructs a constructor mkConstr :: DataType -> String -> [String] -> Fixity -> Constr -- | This function is now deprecated. Please use mkIntegralConstr -- instead. -- | Deprecated: Use mkIntegralConstr instead mkIntConstr :: DataType -> Integer -> Constr -- | This function is now deprecated. Please use mkRealConstr -- instead. -- | Deprecated: Use mkRealConstr instead mkFloatConstr :: DataType -> Double -> Constr mkIntegralConstr :: (Integral a, Show a) => DataType -> a -> Constr mkRealConstr :: (Real a, Show a) => DataType -> a -> Constr -- | This function is now deprecated. Please use mkCharConstr -- instead. -- | Deprecated: Use mkCharConstr instead mkStringConstr :: DataType -> String -> Constr -- | Makes a constructor for Char. mkCharConstr :: DataType -> Char -> Constr -- | Gets the datatype of a constructor constrType :: Constr -> DataType -- | Public representation of constructors data ConstrRep AlgConstr :: ConIndex -> ConstrRep IntConstr :: Integer -> ConstrRep FloatConstr :: Rational -> ConstrRep CharConstr :: Char -> ConstrRep -- | Gets the public presentation of constructors constrRep :: Constr -> ConstrRep -- | Gets the field labels of a constructor. The list of labels is returned -- in the same order as they were given in the original constructor -- declaration. constrFields :: Constr -> [String] -- | Gets the fixity of a constructor constrFixity :: Constr -> Fixity -- | Gets the index of a constructor (algebraic datatypes only) constrIndex :: Constr -> ConIndex -- | Gets the string for a constructor showConstr :: Constr -> String -- | Lookup a constructor via a string readConstr :: DataType -> String -> Maybe Constr -- | Gets the unqualified type constructor: drop *.*.*... before name tyconUQname :: String -> String -- | Gets the module of a type constructor: take *.*.*... before name tyconModule :: String -> String -- | Build a term skeleton fromConstr :: Data a => Constr -> a -- | Build a term and use a generic function for subterms fromConstrB :: Data a => (forall d. Data d => d) -> Constr -> a -- | Monadic variation on fromConstrB fromConstrM :: (Monad m, Data a) => (forall d. Data d => m d) -> Constr -> m a instance Eq ConstrRep instance Show ConstrRep instance Eq Fixity instance Show Fixity instance Show DataType instance Eq DataRep instance Show DataRep instance (Typeable a, Data b, Ix a) => Data (Array a b) instance Typeable a => Data (ForeignPtr a) instance Typeable a => Data (Ptr a) instance (Data a, Data b, Data c, Data d, Data e, Data f, Data g) => Data (a, b, c, d, e, f, g) instance (Data a, Data b, Data c, Data d, Data e, Data f) => Data (a, b, c, d, e, f) instance (Data a, Data b, Data c, Data d, Data e) => Data (a, b, c, d, e) instance (Data a, Data b, Data c, Data d) => Data (a, b, c, d) instance (Data a, Data b, Data c) => Data (a, b, c) instance (Data a, Data b) => Data (a, b) instance Data () instance (Data a, Data b) => Data (Either a b) instance Data Ordering instance Data a => Data (Maybe a) instance Data a => Data [a] instance (Data a, Integral a) => Data (Ratio a) instance Data Word64 instance Data Word32 instance Data Word16 instance Data Word8 instance Data Word instance Data Int64 instance Data Int32 instance Data Int16 instance Data Int8 instance Data Integer instance Data Int instance Data Double instance Data Float instance Data Char instance Data Bool instance Eq Constr instance Show Constr -- | Monadic zipping (used for monad comprehensions) module Control.Monad.Zip -- | MonadZip type class. Minimal definition: mzip or -- mzipWith -- -- Instances should satisfy the laws: -- --
-- liftM (f *** g) (mzip ma mb) = mzip (liftM f ma) (liftM g mb) ---- --
-- liftM (const ()) ma = liftM (const ()) mb -- ==> -- munzip (mzip ma mb) = (ma, mb) --class Monad m => MonadZip m where mzip = mzipWith (,) mzipWith f ma mb = liftM (uncurry f) (mzip ma mb) munzip mab = (liftM fst mab, liftM snd mab) mzip :: MonadZip m => m a -> m b -> m (a, b) mzipWith :: MonadZip m => (a -> b -> c) -> m a -> m b -> m c munzip :: MonadZip m => m (a, b) -> (m a, m b) instance [safe] MonadZip [] -- | This module provides scalable event notification for file descriptors -- and timeouts. -- -- This module should be considered GHC internal. -- --
-- trace ("calling f with x = " ++ show x) (f x) ---- -- The trace function should only be used for debugging, or -- for monitoring execution. The function is not referentially -- transparent: its type indicates that it is a pure function but it has -- the side effect of outputting the trace message. trace :: String -> a -> a -- | Like trace, but uses show on the argument to convert it -- to a String. -- -- This makes it convenient for printing the values of interesting -- variables or expressions inside a function. For example here we print -- the value of the variables x and z: -- --
-- f x y = -- traceShow (x, z) $ result -- where -- z = ... -- ... --traceShow :: Show a => a -> b -> b -- | like trace, but additionally prints a call stack if one is -- available. -- -- In the current GHC implementation, the call stack is only availble if -- the program was compiled with -prof; otherwise -- traceStack behaves exactly like trace. Entries in the -- call stack correspond to SCC annotations, so it is a good -- idea to use -fprof-auto or -fprof-auto-calls to add -- SCC annotations automatically. traceStack :: String -> a -> a -- | The traceIO function outputs the trace message from the IO -- monad. This sequences the output with respect to other IO actions. traceIO :: String -> IO () -- | Deprecated. Use traceIO. -- | Deprecated: Use Debug.Trace.traceIO putTraceMsg :: String -> IO () -- | The traceEvent function behaves like trace with the -- difference that the message is emitted to the eventlog, if eventlog -- profiling is available and enabled at runtime. -- -- It is suitable for use in pure code. In an IO context use -- traceEventIO instead. -- -- Note that when using GHC's SMP runtime, it is possible (but rare) to -- get duplicate events emitted if two CPUs simultaneously evaluate the -- same thunk that uses traceEvent. traceEvent :: String -> a -> a -- | The traceEventIO function emits a message to the eventlog, if -- eventlog profiling is available and enabled at runtime. -- -- Compared to traceEvent, traceEventIO sequences the event -- with respect to other IO actions. traceEventIO :: String -> IO () -- | GHC Extensions: this is the Approved Way to get at GHC-specific -- extensions. module GHC.Exts -- | A fixed-precision integer type with at least the range [-2^29 .. -- 2^29-1]. The exact range for a given implementation can be -- determined by using minBound and maxBound from the -- Bounded class. data Int :: * I# :: Int# -> Int -- | A Word is an unsigned integral type, with the same size as -- Int. data Word W# :: Word# -> Word -- | Single-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- single-precision type. data Float :: * F# :: Float# -> Float -- | Double-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- double-precision type. data Double :: * D# :: Double# -> Double -- | The character type Char is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) characters (see -- http://www.unicode.org/ for details). This set extends the ISO -- 8859-1 (Latin-1) character set (the first 256 characters), which is -- itself an extension of the ASCII character set (the first 128 -- characters). A character literal in Haskell has type Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char :: * C# :: Char# -> Char -- | A value of type Ptr a represents a pointer to an -- object, or an array of objects, which may be marshalled to or from -- Haskell values of type a. -- -- The type a will often be an instance of class Storable -- which provides the marshalling operations. However this is not -- essential, and you can provide your own operations to access the -- pointer. For example you might write small foreign functions to get or -- set the fields of a C struct. data Ptr a Ptr :: Addr# -> Ptr a -- | A value of type FunPtr a is a pointer to a function -- callable from foreign code. The type a will normally be a -- foreign type, a function type with zero or more arguments where -- --
-- foreign import ccall "stdlib.h &free" -- p_free :: FunPtr (Ptr a -> IO ()) ---- -- or a pointer to a Haskell function created using a wrapper stub -- declared to produce a FunPtr of the correct type. For example: -- --
-- type Compare = Int -> Int -> Bool -- foreign import ccall "wrapper" -- mkCompare :: Compare -> IO (FunPtr Compare) ---- -- Calls to wrapper stubs like mkCompare allocate storage, which -- should be released with freeHaskellFunPtr when no longer -- required. -- -- To convert FunPtr values to corresponding Haskell functions, -- one can define a dynamic stub for the specific foreign type, -- e.g. -- --
-- type IntFunction = CInt -> IO () -- foreign import ccall "dynamic" -- mkFun :: FunPtr IntFunction -> IntFunction --data FunPtr a FunPtr :: Addr# -> FunPtr a maxTupleSize :: Int -- | Shift the argument left by the specified number of bits (which must be -- non-negative). shiftL# :: Word# -> Int# -> Word# -- | Shift the argument right by the specified number of bits (which must -- be non-negative). shiftRL# :: Word# -> Int# -> Word# -- | Shift the argument left by the specified number of bits (which must be -- non-negative). iShiftL# :: Int# -> Int# -> Int# -- | Shift the argument right (signed) by the specified number of bits -- (which must be non-negative). iShiftRA# :: Int# -> Int# -> Int# -- | Shift the argument right (unsigned) by the specified number of bits -- (which must be non-negative). iShiftRL# :: Int# -> Int# -> Int# uncheckedShiftL64# :: Word# -> Int# -> Word# uncheckedShiftRL64# :: Word# -> Int# -> Word# uncheckedIShiftL64# :: Int# -> Int# -> Int# uncheckedIShiftRA64# :: Int# -> Int# -> Int# -- | A list producer that can be fused with foldr. This function is -- merely -- --
-- build g = g (:) [] ---- -- but GHC's simplifier will transform an expression of the form -- foldr k z (build g), which may arise after -- inlining, to g k z, which avoids producing an intermediate -- list. build :: (forall b. (a -> b -> b) -> b -> b) -> [a] -- | A list producer that can be fused with foldr. This function is -- merely -- --
-- augment g xs = g (:) xs ---- -- but GHC's simplifier will transform an expression of the form -- foldr k z (augment g xs), which may arise after -- inlining, to g k (foldr k z xs), which avoids -- producing an intermediate list. augment :: (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] -- | Class for string-like datastructures; used by the overloaded string -- extension (-foverloaded-strings in GHC). class IsString a fromString :: IsString a => String -> a breakpoint :: a -> a breakpointCond :: Bool -> a -> a -- | The call '(lazy e)' means the same as e, but lazy has -- a magical strictness property: it is lazy in its first argument, even -- though its semantics is strict. lazy :: a -> a -- | The call '(inline f)' reduces to f, but inline has a -- BuiltInRule that tries to inline f (if it has an unfolding) -- unconditionally The NOINLINE pragma arranges that inline only -- gets inlined (and hence eliminated) late in compilation, after the -- rule has had a good chance to fire. inline :: a -> a -- | The Down type allows you to reverse sort order conveniently. A -- value of type Down a contains a value of type -- a (represented as Down a). If a has -- an Ord instance associated with it then comparing two -- values thus wrapped will give you the opposite of their normal sort -- order. This is particularly useful when sorting in generalised list -- comprehensions, as in: then sortWith by Down x newtype Down a Down :: a -> Down a -- | The groupWith function uses the user supplied function which -- projects an element out of every list element in order to to first -- sort the input list and then to form groups by equality on these -- projected elements groupWith :: Ord b => (a -> b) -> [a] -> [[a]] -- | The sortWith function sorts a list of elements using the user -- supplied function to project something out of each element sortWith :: Ord b => (a -> b) -> [a] -> [a] -- | the ensures that all the elements of the list are identical and -- then returns that unique element the :: Eq a => [a] -> a -- | Deprecated: Use Debug.Trace.traceEvent or -- Debug.Trace.traceEventIO traceEvent :: String -> IO () data SpecConstrAnnotation NoSpecConstr :: SpecConstrAnnotation ForceSpecConstr :: SpecConstrAnnotation -- | returns a '[String]' representing the current call stack. This can be -- useful for debugging. -- -- The implementation uses the call-stack simulation maintined by the -- profiler, so it only works if the program was compiled with -- -prof and contains suitable SCC annotations (e.g. by using -- -fprof-auto). Otherwise, the list returned is likely to be -- empty or uninformative. currentCallStack :: IO [String] data Constraint :: BOX instance Typeable SpecConstrAnnotation instance Eq a => Eq (Down a) instance Data SpecConstrAnnotation instance Eq SpecConstrAnnotation instance Ord a => Ord (Down a) -- | This module provides access to internal garbage collection and memory -- usage statistics. These statistics are not available unless a program -- is run with the -T RTS flag. -- -- This module is GHC-only and should not be considered portable. module GHC.Stats -- | Global garbage collection and memory statistics. data GCStats GCStats :: !Int64 -> !Int64 -> !Int64 -> !Int64 -> !Int64 -> !Int64 -> !Int64 -> !Int64 -> !Int64 -> !Int64 -> !Double -> !Double -> !Double -> !Double -> !Double -> !Double -> !Int64 -> !Int64 -> GCStats -- | Total number of bytes allocated bytesAllocated :: GCStats -> !Int64 -- | Number of garbage collections performed numGcs :: GCStats -> !Int64 -- | Maximum number of live bytes seen so far maxBytesUsed :: GCStats -> !Int64 -- | Number of byte usage samples taken | Sum of all byte usage samples, -- can be used with numByteUsageSamples to calculate averages with -- arbitrary weighting (if you are sampling this record multiple times). numByteUsageSamples :: GCStats -> !Int64 cumulativeBytesUsed :: GCStats -> !Int64 -- | Number of bytes copied during GC bytesCopied :: GCStats -> !Int64 -- | Current number of live bytes currentBytesUsed :: GCStats -> !Int64 -- | Current number of bytes lost to slop currentBytesSlop :: GCStats -> !Int64 -- | Maximum number of bytes lost to slop at any one time so far maxBytesSlop :: GCStats -> !Int64 -- | Maximum number of megabytes allocated | CPU time spent running mutator -- threads. This does not include any profiling overhead or -- initialization. peakMegabytesAllocated :: GCStats -> !Int64 mutatorCpuSeconds :: GCStats -> !Double -- | Wall clock time spent running mutator threads. This does not include -- initialization. mutatorWallSeconds :: GCStats -> !Double -- | CPU time spent running GC gcCpuSeconds :: GCStats -> !Double -- | Wall clock time spent running GC gcWallSeconds :: GCStats -> !Double -- | Total CPU time elapsed since program start cpuSeconds :: GCStats -> !Double -- | Total wall clock time elapsed since start | Number of bytes copied -- during GC, minus space held by mutable lists held by the capabilities. -- Can be used with parMaxBytesCopied to determine how well -- parallel GC utilized all cores. wallSeconds :: GCStats -> !Double parAvgBytesCopied :: GCStats -> !Int64 -- | Sum of number of bytes copied each GC by the most active GC thread -- each GC. The ratio of parAvgBytesCopied divided by -- parMaxBytesCopied approaches 1 for a maximally sequential run -- and approaches the number of threads (set by the RTS flag -N) -- for a maximally parallel run. parMaxBytesCopied :: GCStats -> !Int64 -- | Retrieves garbage collection and memory statistics as of the last -- garbage collection. If you would like your statistics as recent as -- possible, first run a performGC. getGCStats :: IO GCStats instance [safe] Show GCStats instance [safe] Read GCStats -- | An abstract interface to a unique symbol generator. module Data.Unique -- | An abstract unique object. Objects of type Unique may be -- compared for equality and ordering and hashed into Int. data Unique -- | Creates a new object of type Unique. The value returned will -- not compare equal to any other value of type Unique returned by -- previous calls to newUnique. There is no limit on the number of -- times newUnique may be called. newUnique :: IO Unique -- | Hashes a Unique into an Int. Two Uniques may hash -- to the same value, although in practice this is unlikely. The -- Int returned makes a good hash key. hashUnique :: Unique -> Int instance Typeable Unique instance Eq Unique instance Ord Unique -- | Functor and Monad instances for (->) r and -- Functor instances for (,) a and Either -- a. module Control.Monad.Instances -- | The Functor class is used for types that can be mapped over. -- Instances of Functor should satisfy the following laws: -- --
-- fmap id == id -- fmap (f . g) == fmap f . fmap g ---- -- The instances of Functor for lists, Maybe and IO -- satisfy these laws. class Functor f where <$ = fmap . const fmap :: Functor f => (a -> b) -> f a -> f b -- | The Monad class defines the basic operations over a -- monad, a concept from a branch of mathematics known as -- category theory. From the perspective of a Haskell programmer, -- however, it is best to think of a monad as an abstract datatype -- of actions. Haskell's do expressions provide a convenient -- syntax for writing monadic expressions. -- -- Minimal complete definition: >>= and return. -- -- Instances of Monad should satisfy the following laws: -- --
-- return a >>= k == k a -- m >>= return == m -- m >>= (\x -> k x >>= h) == (m >>= k) >>= h ---- -- Instances of both Monad and Functor should additionally -- satisfy the law: -- --
-- fmap f xs == xs >>= return . f ---- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Monad m where m >> k = m >>= \ _ -> k fail s = error s (>>=) :: Monad m => m a -> (a -> m b) -> m b (>>) :: Monad m => m a -> m b -> m b return :: Monad m => a -> m a fail :: Monad m => String -> m a instance [safe] Monad (Either e) instance [safe] Functor (Either a) instance [safe] Functor ((,) a) instance [safe] Monad ((->) r) instance [safe] Functor ((->) r) -- | Functors: uniform action over a parameterized type, generalizing the -- map function on lists. module Data.Functor -- | The Functor class is used for types that can be mapped over. -- Instances of Functor should satisfy the following laws: -- --
-- fmap id == id -- fmap (f . g) == fmap f . fmap g ---- -- The instances of Functor for lists, Maybe and IO -- satisfy these laws. class Functor f where <$ = fmap . const fmap :: Functor f => (a -> b) -> f a -> f b (<$) :: Functor f => a -> f b -> f a -- | An infix synonym for fmap. (<$>) :: Functor f => (a -> b) -> f a -> f b -- | Unbounded channels. module Control.Concurrent.Chan -- | Chan is an abstract type representing an unbounded FIFO -- channel. data Chan a -- | Build and returns a new instance of Chan. newChan :: IO (Chan a) -- | Write a value to a Chan. writeChan :: Chan a -> a -> IO () -- | Read the next value from the Chan. readChan :: Chan a -> IO a -- | Duplicate a Chan: the duplicate channel begins empty, but data -- written to either channel from then on will be available from both. -- Hence this creates a kind of broadcast channel, where data written by -- anyone is seen by everyone else. -- -- (Note that a duplicated channel is not equal to its original. So: -- fmap (c /=) $ dupChan c returns True for all -- c.) dupChan :: Chan a -> IO (Chan a) -- | Put a data item back onto a channel, where it will be the next item -- read. -- | Deprecated: if you need this operation, use -- Control.Concurrent.STM.TChan instead. See -- http://hackage.haskell.org/trac/ghc/ticket/4154 for details unGetChan :: Chan a -> a -> IO () -- | Returns True if the supplied Chan is empty. -- | Deprecated: if you need this operation, use -- Control.Concurrent.STM.TChan instead. See -- http://hackage.haskell.org/trac/ghc/ticket/4154 for details isEmptyChan :: Chan a -> IO Bool -- | Return a lazy list representing the contents of the supplied -- Chan, much like hGetContents. getChanContents :: Chan a -> IO [a] -- | Write an entire list of items to a Chan. writeList2Chan :: Chan a -> [a] -> IO () instance Typeable1 Chan instance Eq (Chan a) -- | Simple quantity semaphores. module Control.Concurrent.QSem -- | A QSem is a simple quantity semaphore, in which the available -- "quantity" is always dealt with in units of one. data QSem -- | Build a new QSem with a supplied initial quantity. The initial -- quantity must be at least 0. newQSem :: Int -> IO QSem -- | Wait for a unit to become available waitQSem :: QSem -> IO () -- | Signal that a unit of the QSem is available signalQSem :: QSem -> IO () instance Typeable QSem instance Eq QSem -- | Quantity semaphores in which each thread may wait for an arbitrary -- "amount". module Control.Concurrent.QSemN -- | A QSemN is a quantity semaphore, in which the available -- "quantity" may be signalled or waited for in arbitrary amounts. data QSemN -- | Build a new QSemN with a supplied initial quantity. The initial -- quantity must be at least 0. newQSemN :: Int -> IO QSemN -- | Wait for the specified quantity to become available waitQSemN :: QSemN -> Int -> IO () -- | Signal that a given quantity is now available from the QSemN. signalQSemN :: QSemN -> Int -> IO () instance Typeable QSemN instance Eq QSemN -- | Sample variables module Control.Concurrent.SampleVar -- | Sample variables are slightly different from a normal MVar: -- --
-- ... 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. forkIOWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | killThread raises the ThreadKilled exception in the -- given thread (GHC only). -- --
-- killThread tid = throwTo tid ThreadKilled --killThread :: ThreadId -> IO () -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. This is a useful property to -- know when dealing with race conditions: eg. if there are two threads -- that can kill each other, it is guaranteed that only one of the -- threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () -- | Like forkIO, but lets you specify on which processor the thread -- should run. Unlike a forkIO thread, a thread created by -- forkOn will stay on the same processor for its entire lifetime -- (forkIO threads can migrate between processors 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 perforamnce in some cases - -- experimentation is recommended). forkOn :: Int -> IO () -> IO ThreadId -- | Like forkIOWithUnmask, but the child thread is pinned to the -- given CPU, as with forkOn. forkOnWithUnmask :: Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | Returns the number of Haskell threads that can run truly -- simultaneously (on separate physical processors) at any given time. -- The number passed to forkOn is interpreted modulo this value. -- -- An implementation in which Haskell threads are mapped directly to OS -- threads might return the number of physical processor cores in the -- machine, and forkOn would be implemented using the OS's -- affinity facilities. An implementation that schedules Haskell threads -- onto a smaller number of OS threads (like GHC) would return the number -- of such OS threads that can be running simultaneously. -- -- GHC notes: this returns the number passed as the argument to the -- +RTS -N flag. In current implementations, the value is fixed -- when the program starts and never changes, but it is possible that in -- the future the number of capabilities might vary at runtime. getNumCapabilities :: IO Int -- | returns the number of the capability on which the thread is currently -- running, and a boolean indicating whether the thread is locked to that -- capability or not. A thread is locked to a capability if it was -- created with forkOn. threadCapability :: ThreadId -> IO (Int, Bool) -- | The yield action allows (forces, in a co-operative multitasking -- implementation) a context-switch to any other currently runnable -- threads (if any), and is occasionally useful when implementing -- concurrency abstractions. yield :: IO () -- | Suspends the current thread for a given number of microseconds (GHC -- only). -- -- There is no guarantee that the thread will be rescheduled promptly -- when the delay has expired, but the thread will never continue to run -- earlier than specified. threadDelay :: Int -> IO () -- | Block the current thread until data is available to read on the given -- file descriptor (GHC only). -- -- This will throw an IOError if the file descriptor was closed -- while this thread was blocked. To safely close a file descriptor that -- has been used with threadWaitRead, use closeFdWith. threadWaitRead :: Fd -> IO () -- | Block the current thread until data can be written to the given file -- descriptor (GHC only). -- -- This will throw an IOError if the file descriptor was closed -- while this thread was blocked. To safely close a file descriptor that -- has been used with threadWaitWrite, use closeFdWith. threadWaitWrite :: Fd -> IO () mergeIO :: [a] -> [a] -> IO [a] nmergeIO :: [[a]] -> IO [a] -- | True if bound threads are supported. If -- rtsSupportsBoundThreads is False, -- isCurrentThreadBound will always return False and both -- forkOS and runInBoundThread will fail. rtsSupportsBoundThreads :: Bool -- | 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. forkOS :: IO () -> IO ThreadId -- | Returns True if the calling thread is bound, that is, if -- it is safe to use foreign libraries that rely on thread-local state -- from the calling thread. isCurrentThreadBound :: IO Bool -- | Run the IO computation passed as the first argument. If the -- calling thread is not bound, a bound thread is created -- temporarily. runInBoundThread doesn't finish until the -- IO computation finishes. -- -- You can wrap a series of foreign function calls that rely on -- thread-local state with runInBoundThread so that you can use -- them without knowing whether the current thread is bound. runInBoundThread :: IO a -> IO a -- | Run the IO computation passed as the first argument. If the -- calling thread is bound, an unbound thread is created -- temporarily using forkIO. runInBoundThread doesn't -- finish until the IO computation finishes. -- -- Use this function only in the rare case that you have actually -- observed a performance loss due to the use of bound threads. A program -- that doesn't need it's main thread to be bound and makes heavy -- use of concurrency (e.g. a web server), might want to wrap it's -- main action in runInUnboundThread. -- -- Note that exceptions which are thrown to the current thread are thrown -- in turn to the thread that is executing the given computation. This -- ensures there's always a way of killing the forked thread. runInUnboundThread :: IO a -> IO a -- | This function is deprecated; use forkIOWIthUnmask instead forkIOUnmasked :: IO () -> IO ThreadId -- | Attach a timeout event to arbitrary IO computations. module System.Timeout -- | Wrap an IO computation to time out and return Nothing -- in case no result is available within n microseconds -- (1/10^6 seconds). In case a result is available before the -- timeout expires, Just a is returned. A negative timeout -- interval means "wait indefinitely". When specifying long timeouts, be -- careful not to exceed maxBound :: Int. -- -- The design of this combinator was guided by the objective that -- timeout n f should behave exactly the same as f as -- long as f doesn't time out. This means that f has -- the same myThreadId it would have without the timeout wrapper. -- Any exceptions f might throw cancel the timeout and propagate -- further up. It also possible for f to receive exceptions -- thrown to it by another thread. -- -- A tricky implementation detail is the question of how to abort an -- IO computation. This combinator relies on asynchronous -- exceptions internally. The technique works very well for computations -- executing inside of the Haskell runtime system, but it doesn't work at -- all for non-Haskell code. Foreign function calls, for example, cannot -- be timed out with this combinator simply because an arbitrary C -- function cannot receive asynchronous exceptions. When timeout -- is used to wrap an FFI call that blocks, no timeout event can be -- delivered until the FFI call returns, which pretty much negates the -- purpose of the combinator. In practice, however, this limitation is -- less severe than it may sound. Standard I/O functions like -- hGetBuf, hPutBuf, Network.Socket.accept, or -- hWaitForInput appear to be blocking, but they really don't -- because the runtime system uses scheduling mechanisms like -- select(2) to perform asynchronous I/O, so it is possible to -- interrupt standard socket I/O or file I/O using this combinator. timeout :: Int -> IO a -> IO (Maybe a) instance Typeable Timeout instance Eq Timeout instance Exception Timeout instance Show Timeout -- | Simple combinators working solely on and with functions. module Data.Function -- | Identity function. id :: a -> a -- | Constant function. const :: a -> b -> a -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c -- | flip f takes its (first) two arguments in the reverse -- order of f. flip :: (a -> b -> c) -> b -> a -> c -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ has low, right-associative binding precedence, so it -- sometimes allows parentheses to be omitted; for example: -- --
-- f $ g $ h x = f (g (h x)) ---- -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. ($) :: (a -> b) -> a -> b -- | fix f is the least fixed point of the function -- f, i.e. the least defined x such that f x = -- x. fix :: (a -> a) -> a -- | (*) `on` f = \x y -> f x * f y. -- -- Typical usage: sortBy (compare `on` -- fst). -- -- Algebraic properties: -- --
((*) `on` f) `on` g = (*) `on` (f . g)
flip on f . flip on g = flip on (g . -- f)
arr id = id
arr (f >>> g) = arr f >>> -- arr g
first (arr f) = arr (first -- f)
first (f >>> g) = first f >>> -- first g
first f >>> arr fst = -- arr fst >>> f
first f >>> arr (id *** g) = -- arr (id *** g) >>> first f
first (first f) >>> arr -- assoc = arr assoc >>> first -- f
-- assoc ((a,b),c) = (a,(b,c)) ---- -- The other combinators have sensible default definitions, which may be -- overridden for efficiency. class Category a => Arrow a where second f = arr swap >>> first f >>> arr swap where swap :: (x, y) -> (y, x) swap ~(x, y) = (y, x) f *** g = first f >>> second g f &&& g = arr (\ b -> (b, b)) >>> f *** g arr :: Arrow a => (b -> c) -> a b c first :: Arrow a => a b c -> a (b, d) (c, d) second :: Arrow a => a b c -> a (d, b) (d, c) (***) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c') (&&&) :: Arrow a => a b c -> a b c' -> a b (c, c') -- | Kleisli arrows of a monad. newtype Kleisli m a b Kleisli :: (a -> m b) -> Kleisli m a b runKleisli :: Kleisli m a b -> a -> m b -- | The identity arrow, which plays the role of return in arrow -- notation. returnA :: Arrow a => a b b -- | Precomposition with a pure function. (^>>) :: Arrow a => (b -> c) -> a c d -> a b d -- | Postcomposition with a pure function. (>>^) :: Arrow a => a b c -> (c -> d) -> a b d -- | Left-to-right composition (>>>) :: Category cat => cat a b -> cat b c -> cat a c -- | Right-to-left composition (<<<) :: Category cat => cat b c -> cat a b -> cat a c -- | Precomposition with a pure function (right-to-left variant). (<<^) :: Arrow a => a c d -> (b -> c) -> a b d -- | Postcomposition with a pure function (right-to-left variant). (^<<) :: Arrow a => (c -> d) -> a b c -> a b d class Arrow a => ArrowZero a zeroArrow :: ArrowZero a => a b c -- | A monoid on arrows. class ArrowZero a => ArrowPlus a (<+>) :: ArrowPlus a => a b c -> a b c -> a b c -- | Choice, for arrows that support it. This class underlies the -- if and case constructs in arrow notation. Minimal -- complete definition: left, satisfying the laws -- --
left (arr f) = arr (left -- f)
left (f >>> g) = left f >>> -- left g
left f >>> arr Left = -- arr Left >>> f
left f >>> arr (id +++ g) = -- arr (id +++ g) >>> left f
left (left f) >>> arr -- assocsum = arr assocsum >>> -- left f
-- assocsum (Left (Left x)) = Left x -- assocsum (Left (Right y)) = Right (Left y) -- assocsum (Right z) = Right (Right z) ---- -- The other combinators have sensible default definitions, which may be -- overridden for efficiency. class Arrow a => ArrowChoice a where right f = arr mirror >>> left f >>> arr mirror where mirror :: Either x y -> Either y x mirror (Left x) = Right x mirror (Right y) = Left y f +++ g = left f >>> right g f ||| g = f +++ g >>> arr untag where untag (Left x) = x untag (Right y) = y left :: ArrowChoice a => a b c -> a (Either b d) (Either c d) right :: ArrowChoice a => a b c -> a (Either d b) (Either d c) (+++) :: ArrowChoice a => a b c -> a b' c' -> a (Either b b') (Either c c') (|||) :: ArrowChoice a => a b d -> a c d -> a (Either b c) d -- | Some arrows allow application of arrow inputs to other inputs. -- Instances should satisfy the following laws: -- --
first (arr (\x -> arr (\y -> -- (x,y)))) >>> app = id
first (arr (g >>>)) >>> -- app = second g >>> app
first (arr (>>> h)) >>> -- app = app >>> h
-- assoc ((a,b),c) = (a,(b,c)) -- unassoc (a,(b,c)) = ((a,b),c) --class Arrow a => ArrowLoop a loop :: ArrowLoop a => a (b, d) (c, d) -> a b c instance MonadFix m => ArrowLoop (Kleisli m) instance ArrowLoop (->) instance ArrowApply a => Monad (ArrowMonad a) instance Monad m => ArrowApply (Kleisli m) instance ArrowApply (->) instance Monad m => ArrowChoice (Kleisli m) instance ArrowChoice (->) instance MonadPlus m => ArrowPlus (Kleisli m) instance MonadPlus m => ArrowZero (Kleisli m) instance Monad m => Arrow (Kleisli m) instance Monad m => Category (Kleisli m) instance Arrow (->) -- | Support code for desugaring in GHC module GHC.Desugar (>>>) :: Arrow arr => forall a b c. arr a b -> arr b c -> arr a c data AnnotationWrapper AnnotationWrapper :: a -> AnnotationWrapper toAnnotationWrapper :: Data a => a -> AnnotationWrapper -- | This library provides support for strict state threads, as -- described in the PLDI '94 paper by John Launchbury and Simon Peyton -- Jones Lazy Functional State Threads. -- -- Safe API Only. module Control.Monad.ST.Safe -- | The strict state-transformer monad. A computation of type -- ST s a transforms an internal state indexed by -- s, and returns a value of type a. The s -- parameter is either -- --
-- runST (writeSTRef _|_ v >>= f) = _|_ --data ST s a -- | Return the value computed by a state transformer computation. The -- forall ensures that the internal state used by the ST -- computation is inaccessible to the rest of the program. runST :: (forall s. ST s a) -> a -- | Allow the result of a state transformer computation to be used -- (lazily) inside the computation. Note that if f is strict, -- fixST f = _|_. fixST :: (a -> ST s a) -> ST s a -- | RealWorld is deeply magical. It is primitive, but it -- is not unlifted (hence ptrArg). We never manipulate -- values of type RealWorld; it's only used in the type system, -- to parameterise State#. data RealWorld :: * -- | A monad transformer embedding strict state transformers in the -- IO monad. The RealWorld parameter indicates that the -- internal state used by the ST computation is a special one -- supplied by the IO monad, and thus distinct from those used by -- invocations of runST. stToIO :: ST RealWorld a -> IO a -- | This library provides support for strict state threads, as -- described in the PLDI '94 paper by John Launchbury and Simon Peyton -- Jones Lazy Functional State Threads. -- -- Unsafe API. module Control.Monad.ST.Unsafe unsafeInterleaveST :: ST s a -> ST s a unsafeIOToST :: IO a -> ST s a unsafeSTToIO :: ST s a -> IO a -- | This library provides support for strict state threads, as -- described in the PLDI '94 paper by John Launchbury and Simon Peyton -- Jones Lazy Functional State Threads. module Control.Monad.ST -- | The strict state-transformer monad. A computation of type -- ST s a transforms an internal state indexed by -- s, and returns a value of type a. The s -- parameter is either -- --
-- runST (writeSTRef _|_ v >>= f) = _|_ --data ST s a -- | Return the value computed by a state transformer computation. The -- forall ensures that the internal state used by the ST -- computation is inaccessible to the rest of the program. runST :: (forall s. ST s a) -> a -- | Allow the result of a state transformer computation to be used -- (lazily) inside the computation. Note that if f is strict, -- fixST f = _|_. fixST :: (a -> ST s a) -> ST s a -- | RealWorld is deeply magical. It is primitive, but it -- is not unlifted (hence ptrArg). We never manipulate -- values of type RealWorld; it's only used in the type system, -- to parameterise State#. data RealWorld :: * -- | A monad transformer embedding strict state transformers in the -- IO monad. The RealWorld parameter indicates that the -- internal state used by the ST computation is a special one -- supplied by the IO monad, and thus distinct from those used by -- invocations of runST. stToIO :: ST RealWorld a -> IO a -- | Deprecated: Please import from Control.Monad.ST.Unsafe instead; -- This will be removed in the next release unsafeInterleaveST :: ST s a -> ST s a -- | Deprecated: Please import from Control.Monad.ST.Unsafe instead; -- This will be removed in the next release unsafeIOToST :: IO a -> ST s a -- | Deprecated: Please import from Control.Monad.ST.Unsafe instead; -- This will be removed in the next release unsafeSTToIO :: ST s a -> IO a -- | This module presents an identical interface to -- Control.Monad.ST, except that the monad delays evaluation of -- state operations until a value depending on them is required. -- -- Safe API only. module Control.Monad.ST.Lazy.Safe -- | The lazy state-transformer monad. A computation of type ST -- s a transforms an internal state indexed by s, and -- returns a value of type a. The s parameter is either -- --
-- runST (writeSTRef _|_ v >>= readSTRef _|_ >> return 2) = 2 --data ST s a -- | Return the value computed by a state transformer computation. The -- forall ensures that the internal state used by the ST -- computation is inaccessible to the rest of the program. runST :: (forall s. ST s a) -> a -- | Allow the result of a state transformer computation to be used -- (lazily) inside the computation. Note that if f is strict, -- fixST f = _|_. fixST :: (a -> ST s a) -> ST s a -- | Convert a strict ST computation into a lazy one. The strict -- state thread passed to strictToLazyST is not performed until -- the result of the lazy state thread it returns is demanded. strictToLazyST :: ST s a -> ST s a -- | Convert a lazy ST computation into a strict one. lazyToStrictST :: ST s a -> ST s a -- | RealWorld is deeply magical. It is primitive, but it -- is not unlifted (hence ptrArg). We never manipulate -- values of type RealWorld; it's only used in the type system, -- to parameterise State#. data RealWorld :: * -- | A monad transformer embedding lazy state transformers in the IO -- monad. The RealWorld parameter indicates that the internal -- state used by the ST computation is a special one supplied by -- the IO monad, and thus distinct from those used by invocations -- of runST. stToIO :: ST RealWorld a -> IO a -- | This module describes a structure intermediate between a functor and a -- monad (technically, a strong lax monoidal functor). Compared with -- monads, this interface lacks the full power of the binding operation -- >>=, but -- --
-- u *> v = pure (const id) <*> u <*> v -- u <* v = pure const <*> u <*> v ---- -- As a consequence of these laws, the Functor instance for -- f will satisfy -- --
-- fmap f x = pure f <*> x ---- -- If f is also a Monad, it should satisfy -- pure = return and (<*>) = -- ap (which implies that pure and <*> -- satisfy the applicative functor laws). class Functor f => Applicative f where *> = liftA2 (const id) <* = liftA2 const pure :: Applicative f => a -> f a (<*>) :: Applicative f => f (a -> b) -> f a -> f b (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a -- | A monoid on applicative functors. -- -- Minimal complete definition: empty and <|>. -- -- If defined, some and many should be the least solutions -- of the equations: -- -- class Applicative f => Alternative f where some v = some_v where many_v = some_v <|> pure [] some_v = (:) <$> v <*> many_v many v = many_v where many_v = some_v <|> pure [] some_v = (:) <$> v <*> many_v empty :: Alternative f => f a (<|>) :: Alternative f => f a -> f a -> f a some :: Alternative f => f a -> f [a] many :: Alternative f => f a -> f [a] newtype Const a b Const :: a -> Const a b getConst :: Const a b -> a newtype WrappedMonad m a WrapMonad :: m a -> WrappedMonad m a unwrapMonad :: WrappedMonad m a -> m a newtype WrappedArrow a b c WrapArrow :: a b c -> WrappedArrow a b c unwrapArrow :: WrappedArrow a b c -> a b c -- | Lists, but with an Applicative functor based on zipping, so -- that -- --
-- f <$> ZipList xs1 <*> ... <*> ZipList xsn = ZipList (zipWithn f xs1 ... xsn) --newtype ZipList a ZipList :: [a] -> ZipList a getZipList :: ZipList a -> [a] -- | An infix synonym for fmap. (<$>) :: Functor f => (a -> b) -> f a -> f b -- | Replace all locations in the input with the same value. The default -- definition is fmap . const, but this may be -- overridden with a more efficient version. (<$) :: Functor f => a -> f b -> f a -- | A variant of <*> with the arguments reversed. (<**>) :: Applicative f => f a -> f (a -> b) -> f b -- | Lift a function to actions. This function may be used as a value for -- fmap in a Functor instance. liftA :: Applicative f => (a -> b) -> f a -> f b -- | Lift a binary function to actions. liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c -- | Lift a ternary function to actions. liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d -- | One or none. optional :: Alternative f => f a -> f (Maybe a) instance Applicative ZipList instance Functor ZipList instance (ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) instance Arrow a => Applicative (WrappedArrow a b) instance Arrow a => Functor (WrappedArrow a b) instance MonadPlus m => Alternative (WrappedMonad m) instance Monad m => Applicative (WrappedMonad m) instance Monad m => Functor (WrappedMonad m) instance Monoid m => Applicative (Const m) instance Functor (Const m) instance Applicative (Either e) instance Monoid a => Applicative ((,) a) instance Applicative ((->) a) instance Alternative STM instance Applicative STM instance Applicative (ST s) instance Applicative (ST s) instance Applicative IO instance Alternative [] instance Applicative [] instance Alternative Maybe instance Applicative Maybe -- | Class of data structures that can be folded to a summary value. -- -- Many of these functions generalize Prelude, -- Control.Monad and Data.List functions of the same names -- from lists to any Foldable functor. To avoid ambiguity, either -- import those modules hiding these names or qualify uses of these -- function names with an alias for this module. module Data.Foldable -- | Data structures that can be folded. -- -- Minimal complete definition: foldMap or foldr. -- -- For example, given a data type -- --
-- data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) ---- -- a suitable instance would be -- --
-- instance Foldable Tree where -- foldMap f Empty = mempty -- foldMap f (Leaf x) = f x -- foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r ---- -- This is suitable even for abstract types, as the monoid is assumed to -- satisfy the monoid laws. Alternatively, one could define -- foldr: -- --
-- 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 --class Foldable t where fold = foldMap id foldMap f = foldr (mappend . f) mempty foldr f z t = appEndo (foldMap (Endo . f) t) z foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z foldr1 f xs = fromMaybe (error "foldr1: empty structure") (foldr mf Nothing xs) where mf x Nothing = Just x mf x (Just y) = Just (f x y) foldl1 f xs = fromMaybe (error "foldl1: empty structure") (foldl mf Nothing xs) where mf Nothing y = Just y mf (Just x) y = Just (f x y) fold :: (Foldable t, Monoid m) => t m -> m foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b foldl :: Foldable t => (a -> b -> a) -> a -> t b -> a foldr1 :: Foldable t => (a -> a -> a) -> t a -> a foldl1 :: Foldable t => (a -> a -> a) -> t a -> a -- | Fold over the elements of a structure, associating to the right, but -- strictly. foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Fold over the elements of a structure, associating to the left, but -- strictly. foldl' :: Foldable t => (a -> b -> a) -> a -> t b -> a -- | Monadic fold over the elements of a structure, associating to the -- right, i.e. from right to left. foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b -- | Monadic fold over the elements of a structure, associating to the -- left, i.e. from left to right. foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m a -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and ignore the results. traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () -- | for_ is traverse_ with its arguments flipped. for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () -- | Evaluate each action in the structure from left to right, and ignore -- the results. sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () -- | The sum of a collection of actions, generalizing concat. asum :: (Foldable t, Alternative f) => t (f a) -> f a -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and ignore the results. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () -- | forM_ is mapM_ with its arguments flipped. forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m () -- | Evaluate each monadic action in the structure from left to right, and -- ignore the results. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | The sum of a collection of actions, generalizing concat. msum :: (Foldable t, MonadPlus m) => t (m a) -> m a -- | List of elements of a structure. toList :: Foldable t => t a -> [a] -- | The concatenation of all the elements of a container of lists. concat :: Foldable t => t [a] -> [a] -- | Map a function over all the elements of a container and concatenate -- the resulting lists. concatMap :: Foldable t => (a -> [b]) -> t a -> [b] -- | and returns the conjunction of a container of Bools. For the -- result to be True, the container must be finite; False, -- however, results from a False value finitely far from the left -- end. and :: Foldable t => t Bool -> Bool -- | or returns the disjunction of a container of Bools. For the -- result to be False, the container must be finite; True, -- however, results from a True value finitely far from the left -- end. or :: Foldable t => t Bool -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. any :: Foldable t => (a -> Bool) -> t a -> Bool -- | Determines whether all elements of the structure satisfy the -- predicate. all :: Foldable t => (a -> Bool) -> t a -> Bool -- | The sum function computes the sum of the numbers of a -- structure. sum :: (Foldable t, Num a) => t a -> a -- | The product function computes the product of the numbers of a -- structure. product :: (Foldable t, Num a) => t a -> a -- | The largest element of a non-empty structure. maximum :: (Foldable t, Ord a) => t a -> a -- | The largest element of a non-empty structure with respect to the given -- comparison function. maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | The least element of a non-empty structure. minimum :: (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure with respect to the given -- comparison function. minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | Does the element occur in the structure? elem :: (Foldable t, Eq a) => a -> t a -> Bool -- | notElem is the negation of elem. notElem :: (Foldable t, Eq a) => a -> t a -> Bool -- | The find function takes a predicate and a structure and returns -- the leftmost element of the structure matching the predicate, or -- Nothing if there is no such element. find :: Foldable t => (a -> Bool) -> t a -> Maybe a instance Ix i => Foldable (Array i) instance Foldable [] instance Foldable Maybe -- | Class of data structures that can be traversed from left to right, -- performing an action on each element. -- -- See also -- --
-- data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) ---- -- a suitable instance would be -- --
-- instance Traversable Tree where -- traverse f Empty = pure Empty -- traverse f (Leaf x) = Leaf <$> f x -- traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r ---- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- --
-- runST (writeSTRef _|_ v >>= readSTRef _|_ >> return 2) = 2 --data ST s a -- | Return the value computed by a state transformer computation. The -- forall ensures that the internal state used by the ST -- computation is inaccessible to the rest of the program. runST :: (forall s. ST s a) -> a -- | Allow the result of a state transformer computation to be used -- (lazily) inside the computation. Note that if f is strict, -- fixST f = _|_. fixST :: (a -> ST s a) -> ST s a -- | Convert a strict ST computation into a lazy one. The strict -- state thread passed to strictToLazyST is not performed until -- the result of the lazy state thread it returns is demanded. strictToLazyST :: ST s a -> ST s a -- | Convert a lazy ST computation into a strict one. lazyToStrictST :: ST s a -> ST s a -- | RealWorld is deeply magical. It is primitive, but it -- is not unlifted (hence ptrArg). We never manipulate -- values of type RealWorld; it's only used in the type system, -- to parameterise State#. data RealWorld :: * -- | A monad transformer embedding lazy state transformers in the IO -- monad. The RealWorld parameter indicates that the internal -- state used by the ST computation is a special one supplied by -- the IO monad, and thus distinct from those used by invocations -- of runST. stToIO :: ST RealWorld a -> IO a -- | Deprecated: Please import from Control.Monad.ST.Lazy.Unsafe -- instead; This will be removed in the next release unsafeInterleaveST :: ST s a -> ST s a -- | Deprecated: Please import from Control.Monad.ST.Lazy.Unsafe -- instead; This will be removed in the next release unsafeIOToST :: IO a -> ST s a -- | The strict ST monad (re-export of Control.Monad.ST) module Control.Monad.ST.Strict -- | Complex numbers. module Data.Complex -- | Complex numbers are an algebraic type. -- -- For a complex number z, abs z is a number -- with the magnitude of z, but oriented in the positive real -- direction, whereas signum z has the phase of -- z, but unit magnitude. data Complex a -- | forms a complex number from its real and imaginary rectangular -- components. (:+) :: !a -> !a -> Complex a -- | Extracts the real part of a complex number. realPart :: RealFloat a => Complex a -> a -- | Extracts the imaginary part of a complex number. imagPart :: RealFloat a => Complex a -> a -- | Form a complex number from polar components of magnitude and phase. mkPolar :: RealFloat a => a -> a -> Complex a -- | cis t is a complex value with magnitude 1 and -- phase t (modulo 2*pi). cis :: RealFloat a => a -> Complex a -- | The function polar takes a complex number and returns a -- (magnitude, phase) pair in canonical form: the magnitude is -- nonnegative, and the phase in the range (-pi, -- pi]; if the magnitude is zero, then so is the phase. polar :: RealFloat a => Complex a -> (a, a) -- | The nonnegative magnitude of a complex number. magnitude :: RealFloat a => Complex a -> a -- | The phase of a complex number, in the range (-pi, -- pi]. If the magnitude is zero, then so is the phase. phase :: RealFloat a => Complex a -> a -- | The conjugate of a complex number. conjugate :: RealFloat a => Complex a -> Complex a instance Typeable1 Complex instance Eq a => Eq (Complex a) instance Show a => Show (Complex a) instance Read a => Read (Complex a) instance Data a => Data (Complex a) instance RealFloat a => Floating (Complex a) instance RealFloat a => Fractional (Complex a) instance RealFloat a => Num (Complex a) -- | This module defines a "Fixed" type for fixed-precision arithmetic. The -- parameter to Fixed is any type that's an instance of HasResolution. -- HasResolution has a single method that gives the resolution of the -- Fixed type. -- -- This module also contains generalisations of div, mod, and divmod to -- work with any Real instance. module Data.Fixed -- | generalisation of div to any instance of Real div' :: (Real a, Integral b) => a -> a -> b -- | generalisation of mod to any instance of Real mod' :: Real a => a -> a -> a -- | generalisation of divMod to any instance of Real divMod' :: (Real a, Integral b) => a -> a -> (b, a) -- | The type parameter should be an instance of HasResolution. data Fixed a class HasResolution a resolution :: HasResolution a => p a -> Integer -- | First arg is whether to chop off trailing zeros showFixed :: HasResolution a => Bool -> Fixed a -> String data E0 -- | resolution of 1, this works the same as Integer type Uni = Fixed E0 data E1 -- | resolution of 10^-1 = .1 type Deci = Fixed E1 data E2 -- | resolution of 10^-2 = .01, useful for many monetary currencies type Centi = Fixed E2 data E3 -- | resolution of 10^-3 = .001 type Milli = Fixed E3 data E6 -- | resolution of 10^-6 = .000001 type Micro = Fixed E6 data E9 -- | resolution of 10^-9 = .000000001 type Nano = Fixed E9 data E12 -- | resolution of 10^-12 = .000000000001 type Pico = Fixed E12 instance Typeable1 Fixed instance Typeable E0 instance Typeable E1 instance Typeable E2 instance Typeable E3 instance Typeable E6 instance Typeable E9 instance Typeable E12 instance Eq (Fixed a) instance Ord (Fixed a) instance HasResolution E12 instance HasResolution E9 instance HasResolution E6 instance HasResolution E3 instance HasResolution E2 instance HasResolution E1 instance HasResolution E0 instance HasResolution a => Read (Fixed a) instance HasResolution a => Show (Fixed a) instance HasResolution a => RealFrac (Fixed a) instance HasResolution a => Fractional (Fixed a) instance HasResolution a => Real (Fixed a) instance HasResolution a => Num (Fixed a) instance Enum (Fixed a) instance Typeable a => Data (Fixed a) -- | The Ix class is used to map a contiguous subrange of values in -- type onto integers. It is used primarily for array indexing (see the -- array package). module Data.Ix -- | The Ix class is used to map a contiguous subrange of values in -- a type onto integers. It is used primarily for array indexing (see the -- array package). -- -- The first argument (l,u) of each of these operations is a -- pair specifying the lower and upper bounds of a contiguous subrange of -- values. -- -- An implementation is entitled to assume the following laws about these -- operations: -- --
-- mkWeakPtr key finalizer = mkWeak key key finalizer --mkWeakPtr :: k -> Maybe (IO ()) -> IO (Weak k) -- | A specialised version of mkWeakPtr, where the Weak -- object returned is simply thrown away (however the finalizer will be -- remembered by the garbage collector, and will still be run when the -- key becomes unreachable). -- -- Note: adding a finalizer to a ForeignPtr using -- addFinalizer won't work as well as using the specialised -- version addForeignPtrFinalizer because the latter version adds -- the finalizer to the primitive 'ForeignPtr#' object inside, whereas -- the generic addFinalizer will add the finalizer to the box. -- Optimisations tend to remove the box, which may cause the finalizer to -- run earlier than you intended. The same motivation justifies the -- existence of addMVarFinalizer and mkWeakIORef (the -- non-uniformity is accidental). addFinalizer :: key -> IO () -> IO () -- | A specialised version of mkWeak where the value is actually a -- pair of the key and value passed to mkWeakPair: -- --
-- mkWeakPair key val finalizer = mkWeak key (key,val) finalizer ---- -- The advantage of this is that the key can be retrieved by -- deRefWeak in addition to the value. mkWeakPair :: k -> v -> Maybe (IO ()) -> IO (Weak (k, v)) -- | A C printf like formatter. module Text.Printf -- | Format a variable number of arguments with the C-style formatting -- string. The return value is either String or (IO -- a). -- -- The format string consists of ordinary characters and /conversion -- specifications/, which specify how to format one of the arguments to -- printf in the output string. A conversion specification begins with -- the character %, followed by one or more of the following -- flags: -- --
-- - left adjust (default is right adjust) -- + always use a sign (+ or -) for signed conversions -- 0 pad with zeroes rather than spaces ---- -- followed optionally by a field width: -- --
-- num field width -- * as num, but taken from argument list ---- -- followed optionally by a precision: -- --
-- .num precision (number of decimal places) ---- -- and finally, a format character: -- --
-- c character Char, Int, Integer, ... -- d decimal Char, Int, Integer, ... -- o octal Char, Int, Integer, ... -- x hexadecimal Char, Int, Integer, ... -- X hexadecimal Char, Int, Integer, ... -- u unsigned decimal Char, Int, Integer, ... -- f floating point Float, Double -- g general format float Float, Double -- G general format float Float, Double -- e exponent format float Float, Double -- E exponent format float Float, Double -- s string String ---- -- Mismatch between the argument types and the format string will cause -- an exception to be thrown at runtime. -- -- Examples: -- --
-- > printf "%d\n" (23::Int) -- 23 -- > printf "%s %s\n" "Hello" "World" -- Hello World -- > printf "%.2f\n" pi -- 3.14 --printf :: PrintfType r => String -> r -- | Similar to printf, except that output is via the specified -- Handle. The return type is restricted to (IO -- a). hPrintf :: HPrintfType r => Handle -> String -> r -- | The PrintfType class provides the variable argument magic for -- printf. Its implementation is intentionally not visible from -- this module. If you attempt to pass an argument of a type which is not -- an instance of this class to printf or hPrintf, then the -- compiler will report it as a missing instance of PrintfArg. class PrintfType t -- | The HPrintfType class provides the variable argument magic for -- hPrintf. Its implementation is intentionally not visible from -- this module. class HPrintfType t class PrintfArg a class IsChar c instance [safe] IsChar Char instance [safe] PrintfArg Double instance [safe] PrintfArg Float instance [safe] PrintfArg Integer instance [safe] PrintfArg Word64 instance [safe] PrintfArg Word32 instance [safe] PrintfArg Word16 instance [safe] PrintfArg Word8 instance [safe] PrintfArg Word instance [safe] PrintfArg Int64 instance [safe] PrintfArg Int32 instance [safe] PrintfArg Int16 instance [safe] PrintfArg Int8 instance [safe] PrintfArg Int instance [safe] IsChar c => PrintfArg [c] instance [safe] PrintfArg Char instance [safe] (PrintfArg a, HPrintfType r) => HPrintfType (a -> r) instance [safe] (PrintfArg a, PrintfType r) => PrintfType (a -> r) instance [safe] HPrintfType (IO a) instance [safe] PrintfType (IO a) instance [safe] IsChar c => PrintfType [c] -- | Optional instance of Show for functions: -- --
-- instance Show (a -> b) where -- showsPrec _ _ = showString \"\<function\>\" --module Text.Show.Functions instance [safe] Show (a -> b)