-- 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 @version 4.10.0.0 module GHC.Profiling -- | Stop attributing ticks to cost centres. Allocations will still be -- attributed. stopProfTimer :: IO () -- | Start attributing ticks to cost centres. This is called by the RTS on -- startup. startProfTimer :: IO () module GHC.IO.Encoding.CodePage module GHC.Constants -- | NB. the contents of this module are only available on Windows. -- -- Installing Win32 console handlers. module GHC.ConsoleHandler -- | Functions associated with the tuple data types. module Data.Tuple -- | 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) -- | Swap the components of a pair. swap :: (a, b) -> (b, a) -- | The Maybe type, and associated operations. module Data.Maybe -- | 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. -- --

Examples

-- -- Basic usage: -- --
--   >>> maybe False odd (Just 3)
--   True
--   
-- --
--   >>> maybe False odd Nothing
--   False
--   
-- -- Read an integer from a string using readMaybe. If we succeed, -- return twice the integer; that is, apply (*2) to it. If -- instead we fail to parse an integer, return 0 by default: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> maybe 0 (*2) (readMaybe "5")
--   10
--   
--   >>> maybe 0 (*2) (readMaybe "")
--   0
--   
-- -- Apply show to a Maybe Int. If we have Just -- n, we want to show the underlying Int n. But if -- we have Nothing, we return the empty string instead of (for -- example) "Nothing": -- --
--   >>> maybe "" show (Just 5)
--   "5"
--   
--   >>> maybe "" show Nothing
--   ""
--   
maybe :: b -> (a -> b) -> Maybe a -> b -- | The isJust function returns True iff its argument is of -- the form Just _. -- --

Examples

-- -- Basic usage: -- --
--   >>> isJust (Just 3)
--   True
--   
-- --
--   >>> isJust (Just ())
--   True
--   
-- --
--   >>> isJust Nothing
--   False
--   
-- -- Only the outer constructor is taken into consideration: -- --
--   >>> isJust (Just Nothing)
--   True
--   
isJust :: Maybe a -> Bool -- | The isNothing function returns True iff its argument is -- Nothing. -- --

Examples

-- -- Basic usage: -- --
--   >>> isNothing (Just 3)
--   False
--   
-- --
--   >>> isNothing (Just ())
--   False
--   
-- --
--   >>> isNothing Nothing
--   True
--   
-- -- Only the outer constructor is taken into consideration: -- --
--   >>> isNothing (Just Nothing)
--   False
--   
isNothing :: Maybe a -> Bool -- | The fromJust function extracts the element out of a Just -- and throws an error if its argument is Nothing. -- --

Examples

-- -- Basic usage: -- --
--   >>> fromJust (Just 1)
--   1
--   
-- --
--   >>> 2 * (fromJust (Just 10))
--   20
--   
-- --
--   >>> 2 * (fromJust Nothing)
--   *** Exception: Maybe.fromJust: Nothing
--   
fromJust :: Maybe a -> a -- | The fromMaybe function takes a default value and and -- Maybe value. If the Maybe is Nothing, it returns -- the default values; otherwise, it returns the value contained in the -- Maybe. -- --

Examples

-- -- Basic usage: -- --
--   >>> fromMaybe "" (Just "Hello, World!")
--   "Hello, World!"
--   
-- --
--   >>> fromMaybe "" Nothing
--   ""
--   
-- -- Read an integer from a string using readMaybe. If we fail to -- parse an integer, we want to return 0 by default: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> fromMaybe 0 (readMaybe "5")
--   5
--   
--   >>> fromMaybe 0 (readMaybe "")
--   0
--   
fromMaybe :: a -> Maybe a -> a -- | The listToMaybe function returns Nothing on an empty -- list or Just a where a is the first element -- of the list. -- --

Examples

-- -- Basic usage: -- --
--   >>> listToMaybe []
--   Nothing
--   
-- --
--   >>> listToMaybe [9]
--   Just 9
--   
-- --
--   >>> listToMaybe [1,2,3]
--   Just 1
--   
-- -- Composing maybeToList with listToMaybe should be the -- identity on singleton/empty lists: -- --
--   >>> maybeToList $ listToMaybe [5]
--   [5]
--   
--   >>> maybeToList $ listToMaybe []
--   []
--   
-- -- But not on lists with more than one element: -- --
--   >>> maybeToList $ listToMaybe [1,2,3]
--   [1]
--   
listToMaybe :: [a] -> Maybe a -- | The maybeToList function returns an empty list when given -- Nothing or a singleton list when not given Nothing. -- --

Examples

-- -- Basic usage: -- --
--   >>> maybeToList (Just 7)
--   [7]
--   
-- --
--   >>> maybeToList Nothing
--   []
--   
-- -- One can use maybeToList to avoid pattern matching when combined -- with a function that (safely) works on lists: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> sum $ maybeToList (readMaybe "3")
--   3
--   
--   >>> sum $ maybeToList (readMaybe "")
--   0
--   
maybeToList :: Maybe a -> [a] -- | The catMaybes function takes a list of Maybes and -- returns a list of all the Just values. -- --

Examples

-- -- Basic usage: -- --
--   >>> catMaybes [Just 1, Nothing, Just 3]
--   [1,3]
--   
-- -- When constructing a list of Maybe values, catMaybes can -- be used to return all of the "success" results (if the list is the -- result of a map, then mapMaybe would be more -- appropriate): -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
--   [Just 1,Nothing,Just 3]
--   
--   >>> catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
--   [1,3]
--   
catMaybes :: [Maybe a] -> [a] -- | The mapMaybe function is a version of map which can -- throw out elements. In particular, the functional argument returns -- something of type Maybe b. If this is Nothing, -- no element is added on to the result list. If it is Just -- b, then b is included in the result list. -- --

Examples

-- -- Using mapMaybe f x is a shortcut for -- catMaybes $ map f x in most cases: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> let readMaybeInt = readMaybe :: String -> Maybe Int
--   
--   >>> mapMaybe readMaybeInt ["1", "Foo", "3"]
--   [1,3]
--   
--   >>> catMaybes $ map readMaybeInt ["1", "Foo", "3"]
--   [1,3]
--   
-- -- If we map the Just constructor, the entire list should be -- returned: -- --
--   >>> mapMaybe Just [1,2,3]
--   [1,2,3]
--   
mapMaybe :: (a -> Maybe b) -> [a] -> [b] module GHC.Char -- | The toEnum method restricted to the type Char. chr :: Int -> Char eqChar :: Char -> Char -> Bool neChar :: Char -> Char -> Bool -- | 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 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 -- | 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 infixl 4 <$ -- | Flipped version of <$. -- --

Examples

-- -- Replace the contents of a Maybe Int with a -- constant String: -- --
--   >>> Nothing $> "foo"
--   Nothing
--   
--   >>> Just 90210 $> "foo"
--   Just "foo"
--   
-- -- Replace the contents of an Either Int -- Int with a constant String, resulting in an -- Either Int String: -- --
--   >>> Left 8675309 $> "foo"
--   Left 8675309
--   
--   >>> Right 8675309 $> "foo"
--   Right "foo"
--   
-- -- Replace each element of a list with a constant String: -- --
--   >>> [1,2,3] $> "foo"
--   ["foo","foo","foo"]
--   
-- -- Replace the second element of a pair with a constant String: -- --
--   >>> (1,2) $> "foo"
--   (1,"foo")
--   
($>) :: Functor f => f a -> b -> f b infixl 4 $> -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
--    ($)  ::              (a -> b) ->   a ->   b
--   (<$>) :: Functor f => (a -> b) -> f a -> f b
--   
-- -- Whereas $ is function application, <$> is -- function application lifted over a Functor. -- --

Examples

-- -- Convert from a Maybe Int to a -- Maybe String using show: -- --
--   >>> show <$> Nothing
--   Nothing
--   
--   >>> show <$> Just 3
--   Just "3"
--   
-- -- Convert from an Either Int Int to -- an Either Int String using -- show: -- --
--   >>> show <$> Left 17
--   Left 17
--   
--   >>> show <$> Right 17
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> (*2) <$> [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> even <$> (2,2)
--   (2,True)
--   
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 <$> -- | void value discards or ignores the result of -- evaluation, such as the return value of an IO action. -- --

Examples

-- -- Replace the contents of a Maybe Int with -- unit: -- --
--   >>> void Nothing
--   Nothing
--   
--   >>> void (Just 3)
--   Just ()
--   
-- -- Replace the contents of an Either Int -- Int with unit, resulting in an Either -- Int '()': -- --
--   >>> void (Left 8675309)
--   Left 8675309
--   
--   >>> void (Right 8675309)
--   Right ()
--   
-- -- Replace every element of a list with unit: -- --
--   >>> void [1,2,3]
--   [(),(),()]
--   
-- -- Replace the second element of a pair with unit: -- --
--   >>> void (1,2)
--   (1,())
--   
-- -- Discard the result of an IO action: -- --
--   >>> mapM print [1,2]
--   1
--   2
--   [(),()]
--   
--   >>> void $ mapM print [1,2]
--   1
--   2
--   
void :: Functor f => f a -> f () -- | Simple combinators working solely on and with functions. module Data.Function -- | Identity function. id :: a -> a -- | const x is a unary function which evaluates to x for -- all inputs. -- -- For instance, -- --
--   >>> map (const 42) [0..3]
--   [42,42,42,42]
--   
const :: a -> b -> a -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | 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 infixr 0 $ -- | & is a reverse application operator. This provides -- notational convenience. Its precedence is one higher than that of the -- forward application operator $, which allows & to be -- nested in $. (&) :: a -> (a -> b) -> b infixl 1 & -- | 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 :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 `on` -- | 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 -- | Safe coercions between data types. -- -- More in-depth information can be found on the Roles wiki page module Data.Coerce -- | The function coerce allows you to safely convert between -- values of types that have the same representation with no run-time -- overhead. In the simplest case you can use it instead of a newtype -- constructor, to go from the newtype's concrete type to the abstract -- type. But it also works in more complicated settings, e.g. converting -- a list of newtypes to a list of concrete types. coerce :: Coercible * a b => a -> b -- | Coercible is a two-parameter class that has instances for -- types a and b if the compiler can infer that they -- have the same representation. This class does not have regular -- instances; instead they are created on-the-fly during type-checking. -- Trying to manually declare an instance of Coercible is an -- error. -- -- Nevertheless one can pretend that the following three kinds of -- instances exist. First, as a trivial base-case: -- --
--   instance Coercible a a
--   
-- -- Furthermore, for every type constructor there is an instance that -- allows to coerce under the type constructor. For example, let -- D be a prototypical type constructor (data or -- newtype) with three type arguments, which have roles -- nominal, representational resp. phantom. -- Then there is an instance of the form -- --
--   instance Coercible b b' => Coercible (D a b c) (D a b' c')
--   
-- -- Note that the nominal type arguments are equal, the -- representational type arguments can differ, but need to have -- a Coercible instance themself, and the phantom type -- arguments can be changed arbitrarily. -- -- The third kind of instance exists for every newtype NT = MkNT -- T and comes in two variants, namely -- --
--   instance Coercible a T => Coercible a NT
--   
-- --
--   instance Coercible T b => Coercible NT b
--   
-- -- This instance is only usable if the constructor MkNT is in -- scope. -- -- If, as a library author of a type constructor like Set a, you -- want to prevent a user of your module to write coerce :: Set T -- -> Set NT, you need to set the role of Set's type -- parameter to nominal, by writing -- --
--   type role Set nominal
--   
-- -- For more details about this feature, please refer to Safe -- Coercions by Joachim Breitner, Richard A. Eisenberg, Simon Peyton -- Jones and Stephanie Weirich. class (~R#) k0 k0 a b => Coercible k0 (a :: k0) (b :: k0) -- | The Bool type and related functions. module Data.Bool data Bool :: * False :: Bool True :: Bool -- | Boolean "and" (&&) :: Bool -> Bool -> Bool infixr 3 && -- | Boolean "or" (||) :: Bool -> Bool -> Bool infixr 2 || -- | 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 -- | Case analysis for the Bool type. bool x y p -- evaluates to x when p is False, and evaluates -- to y when p is True. -- -- This is equivalent to if p then y else x; that is, one can -- think of it as an if-then-else construct with its arguments reordered. -- --

Examples

-- -- Basic usage: -- --
--   >>> bool "foo" "bar" True
--   "bar"
--   
--   >>> bool "foo" "bar" False
--   "foo"
--   
-- -- Confirm that bool x y p and if p then y else -- x are equivalent: -- --
--   >>> let p = True; x = "bar"; y = "foo"
--   
--   >>> bool x y p == if p then y else x
--   True
--   
--   >>> let p = False
--   
--   >>> bool x y p == if p then y else x
--   True
--   
bool :: a -> a -> Bool -> a -- | Basic operations on type-level Booleans. module Data.Type.Bool -- | Type-level If. If True a b ==> a; If -- False a b ==> b -- | Type-level "and" -- | Type-level "or" -- | Type-level "not". An injective type family since 4.10.0.0. -- | 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. -- -- class Eq a => Bits a -- | Bitwise "and" (.&.) :: Bits a => a -> a -> a -- | Bitwise "or" (.|.) :: Bits a => a -> a -> a -- | Bitwise "xor" xor :: Bits a => a -> a -> a -- | Reverse all the bits in the argument complement :: Bits a => a -> a -- | shift x i shifts x left by i bits if -- i is positive, or right by -i bits otherwise. Right -- shifts perform sign extension on signed number types; i.e. they fill -- the top bits with 1 if the x is negative and with 0 -- otherwise. -- -- An instance can define either this unified shift or -- shiftL and shiftR, depending on which is more convenient -- for the type in question. shift :: Bits a => a -> Int -> a -- | rotate x i rotates x left by i bits -- if i is positive, or right by -i bits otherwise. -- -- For unbounded types like Integer, rotate is equivalent -- to shift. -- -- An instance can define either this unified rotate or -- rotateL and rotateR, depending on which is more -- convenient for the type in question. rotate :: Bits a => a -> Int -> a -- | zeroBits is the value with all bits unset. -- -- The following laws ought to hold (for all valid bit indices -- n): -- -- -- -- This method uses clearBit (bit 0) 0 as its -- default implementation (which ought to be equivalent to -- zeroBits for types which possess a 0th bit). zeroBits :: Bits a => a -- | bit i is a value with the ith bit set -- and all other bits clear. -- -- Can be implemented using bitDefault if a is also an -- instance of Num. -- -- See also zeroBits. bit :: Bits a => Int -> a -- | x `setBit` i is the same as x .|. bit i setBit :: Bits a => a -> Int -> a -- | x `clearBit` i is the same as x .&. complement (bit -- i) clearBit :: Bits a => a -> Int -> a -- | x `complementBit` i is the same as x `xor` bit i complementBit :: Bits a => a -> Int -> a -- | Return True if the nth bit of the argument is 1 -- -- Can be implemented using testBitDefault if a is also -- an instance of Num. testBit :: Bits a => a -> Int -> Bool -- | Return the number of bits in the type of the argument. The actual -- value of the argument is ignored. Returns Nothing for types that do -- not have a fixed bitsize, like Integer. bitSizeMaybe :: Bits a => a -> Maybe Int -- | Return the number of bits in the type of the argument. The actual -- value of the argument is ignored. The function bitSize is -- undefined for types that do not have a fixed bitsize, like -- Integer. -- | Deprecated: Use bitSizeMaybe or finiteBitSize -- instead bitSize :: Bits a => a -> Int -- | Return True if the argument is a signed type. The actual value -- of the argument is ignored isSigned :: Bits a => a -> Bool -- | Shift the argument left by the specified number of bits (which must be -- non-negative). -- -- An instance can define either this and shiftR or the unified -- shift, depending on which is more convenient for the type in -- question. shiftL :: Bits a => a -> Int -> a -- | Shift the argument left by the specified number of bits. The result is -- undefined for negative shift amounts and shift amounts greater or -- equal to the bitSize. -- -- Defaults to shiftL unless defined explicitly by an instance. unsafeShiftL :: Bits a => a -> Int -> a -- | Shift the first argument right by the specified number of bits. The -- result is undefined for negative shift amounts and shift amounts -- greater or equal to the bitSize. -- -- Right shifts perform sign extension on signed number types; i.e. they -- fill the top bits with 1 if the x is negative and with 0 -- otherwise. -- -- An instance can define either this and shiftL or the unified -- shift, depending on which is more convenient for the type in -- question. shiftR :: Bits a => a -> Int -> a -- | Shift the first argument right by the specified number of bits, which -- must be non-negative an smaller than the number of bits in the type. -- -- Right shifts perform sign extension on signed number types; i.e. they -- fill the top bits with 1 if the x is negative and with 0 -- otherwise. -- -- Defaults to shiftR unless defined explicitly by an instance. unsafeShiftR :: Bits a => a -> Int -> a -- | Rotate the argument left by the specified number of bits (which must -- be non-negative). -- -- An instance can define either this and rotateR or the unified -- rotate, depending on which is more convenient for the type in -- question. rotateL :: Bits a => a -> Int -> a -- | Rotate the argument right by the specified number of bits (which must -- be non-negative). -- -- An instance can define either this and rotateL or the unified -- rotate, depending on which is more convenient for the type in -- question. rotateR :: Bits a => a -> Int -> a -- | Return the number of set bits in the argument. This number is known as -- the population count or the Hamming weight. -- -- Can be implemented using popCountDefault if a is also -- an instance of Num. popCount :: Bits a => a -> Int -- | The FiniteBits class denotes types with a finite, fixed number -- of bits. class Bits b => FiniteBits b -- | Return the number of bits in the type of the argument. The actual -- value of the argument is ignored. Moreover, finiteBitSize is -- total, in contrast to the deprecated bitSize function it -- replaces. -- --
--   finiteBitSize = bitSize
--   bitSizeMaybe = Just . finiteBitSize
--   
finiteBitSize :: FiniteBits b => b -> Int -- | Count number of zero bits preceding the most significant set bit. -- --
--   countLeadingZeros (zeroBits :: a) = finiteBitSize (zeroBits :: a)
--   
-- -- countLeadingZeros can be used to compute log base 2 via -- --
--   logBase2 x = finiteBitSize x - 1 - countLeadingZeros x
--   
-- -- Note: The default implementation for this method is intentionally -- naive. However, the instances provided for the primitive integral -- types are implemented using CPU specific machine instructions. countLeadingZeros :: FiniteBits b => b -> Int -- | Count number of zero bits following the least significant set bit. -- --
--   countTrailingZeros (zeroBits :: a) = finiteBitSize (zeroBits :: a)
--   countTrailingZeros . negate = countTrailingZeros
--   
-- -- The related find-first-set operation can be expressed in terms -- of countTrailingZeros as follows -- --
--   findFirstSet x = 1 + countTrailingZeros x
--   
-- -- Note: The default implementation for this method is intentionally -- naive. However, the instances provided for the primitive integral -- types are implemented using CPU specific machine instructions. countTrailingZeros :: FiniteBits b => b -> Int -- | Default implementation for bit. -- -- Note that: bitDefault i = 1 shiftL i bitDefault :: (Bits a, Num a) => Int -> a -- | Default implementation for testBit. -- -- Note that: testBitDefault x i = (x .&. bit i) /= 0 testBitDefault :: (Bits a, Num a) => a -> Int -> Bool -- | Default implementation for popCount. -- -- This implementation is intentionally naive. Instances are expected to -- provide an optimized implementation for their size. popCountDefault :: (Bits a, Num a) => a -> Int -- | Attempt to convert an Integral type a to an -- Integral type b using the size of the types as -- measured by Bits methods. -- -- A simpler version of this function is: -- --
--   toIntegral :: (Integral a, Integral b) => a -> Maybe b
--   toIntegral x
--     | toInteger x == y = Just (fromInteger y)
--     | otherwise        = Nothing
--     where
--       y = toInteger x
--   
-- -- This version requires going through Integer, which can be -- inefficient. However, toIntegralSized is optimized to allow -- GHC to statically determine the relative type sizes (as measured by -- bitSizeMaybe and isSigned) and avoid going through -- Integer for many types. (The implementation uses -- fromIntegral, which is itself optimized with rules for -- base types but may go through Integer for some type -- pairs.) toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b instance Data.Bits.FiniteBits GHC.Types.Bool instance Data.Bits.Bits GHC.Types.Int instance Data.Bits.FiniteBits GHC.Types.Int instance Data.Bits.Bits GHC.Types.Word instance Data.Bits.FiniteBits GHC.Types.Word instance Data.Bits.Bits GHC.Types.Bool instance Data.Bits.Bits GHC.Integer.Type.Integer -- | Transitional module providing the MonadFail class and primitive -- instances. -- -- This module can be imported for defining forward compatible -- MonadFail instances: -- --
--   import qualified Control.Monad.Fail as Fail
--   
--   instance Monad Foo where
--     (>>=) = {- ...bind impl... -}
--   
--     -- Provide legacy fail implementation for when
--     -- new-style MonadFail desugaring is not enabled.
--     fail = Fail.fail
--   
--   instance Fail.MonadFail Foo where
--     fail = {- ...fail implementation... -}
--   
-- -- See -- https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail -- for more details. module Control.Monad.Fail -- | When a value is bound in do-notation, the pattern on the left -- hand side of <- might not match. In this case, this class -- provides a function to recover. -- -- A Monad without a MonadFail instance may only be used in -- conjunction with pattern that always match, such as newtypes, tuples, -- data types with only a single data constructor, and irrefutable -- patterns (~pat). -- -- Instances of MonadFail should satisfy the following law: -- fail s should be a left zero for >>=, -- --
--   fail s >>= f  =  fail s
--   
-- -- If your Monad is also MonadPlus, a popular definition -- is -- --
--   fail _ = mzero
--   
class Monad m => MonadFail m fail :: MonadFail m => String -> m a instance Control.Monad.Fail.MonadFail GHC.Base.Maybe instance Control.Monad.Fail.MonadFail [] instance Control.Monad.Fail.MonadFail GHC.Types.IO -- | This is a library of parser combinators, originally written by Koen -- Claessen. It parses all alternatives in parallel, so it never keeps -- hold of the beginning of the input string, a common source of space -- leaks with other parsers. The '(+++)' choice combinator is genuinely -- commutative; it makes no difference which branch is "shorter". module Text.ParserCombinators.ReadP data ReadP a -- | Consumes and returns the next character. Fails if there is no input -- left. get :: ReadP Char -- | Look-ahead: returns the part of the input that is left, without -- consuming it. look :: ReadP String -- | Symmetric choice. (+++) :: ReadP a -> ReadP a -> ReadP a infixr 5 +++ -- | Local, exclusive, left-biased choice: If left parser locally produces -- any result at all, then right parser is not used. (<++) :: ReadP a -> ReadP a -> ReadP a infixr 5 <++ -- | Transforms a parser into one that does the same, but in addition -- returns the exact characters read. IMPORTANT NOTE: gather gives -- a runtime error if its first argument is built using any occurrences -- of readS_to_P. gather :: ReadP a -> ReadP (String, a) -- | Always fails. pfail :: ReadP a -- | Succeeds iff we are at the end of input eof :: ReadP () -- | Consumes and returns the next character, if it satisfies the specified -- predicate. satisfy :: (Char -> Bool) -> ReadP Char -- | Parses and returns the specified character. char :: Char -> ReadP Char -- | Parses and returns the specified string. string :: String -> ReadP String -- | Parses the first zero or more characters satisfying the predicate. -- Always succeds, exactly once having consumed all the characters Hence -- NOT the same as (many (satisfy p)) munch :: (Char -> Bool) -> ReadP String -- | Parses the first one or more characters satisfying the predicate. -- Fails if none, else succeeds exactly once having consumed all the -- characters Hence NOT the same as (many1 (satisfy p)) munch1 :: (Char -> Bool) -> ReadP String -- | Skips all whitespace. skipSpaces :: ReadP () -- | Combines all parsers in the specified list. choice :: [ReadP a] -> ReadP a -- | count n p parses n occurrences of p in -- sequence. A list of results is returned. count :: Int -> ReadP a -> ReadP [a] -- | between open close p parses open, followed by -- p and finally close. Only the value of p is -- returned. between :: ReadP open -> ReadP close -> ReadP a -> ReadP a -- | option x p will either parse p or return x -- without consuming any input. option :: a -> ReadP a -> ReadP a -- | optional p optionally parses p and always returns -- (). optional :: ReadP a -> ReadP () -- | Parses zero or more occurrences of the given parser. many :: ReadP a -> ReadP [a] -- | Parses one or more occurrences of the given parser. many1 :: ReadP a -> ReadP [a] -- | Like many, but discards the result. skipMany :: ReadP a -> ReadP () -- | Like many1, but discards the result. skipMany1 :: ReadP a -> ReadP () -- | sepBy p sep parses zero or more occurrences of p, -- separated by sep. Returns a list of values returned by -- p. sepBy :: ReadP a -> ReadP sep -> ReadP [a] -- | sepBy1 p sep parses one or more occurrences of p, -- separated by sep. Returns a list of values returned by -- p. sepBy1 :: ReadP a -> ReadP sep -> ReadP [a] -- | endBy p sep parses zero or more occurrences of p, -- separated and ended by sep. endBy :: ReadP a -> ReadP sep -> ReadP [a] -- | endBy p sep parses one or more occurrences of p, -- separated and ended by sep. endBy1 :: ReadP a -> ReadP sep -> ReadP [a] -- | chainr p op x parses zero or more occurrences of p, -- separated by op. Returns a value produced by a right -- associative application of all functions returned by op. If -- there are no occurrences of p, x is returned. chainr :: ReadP a -> ReadP (a -> a -> a) -> a -> ReadP a -- | chainl p op x parses zero or more occurrences of p, -- separated by op. Returns a value produced by a left -- associative application of all functions returned by op. If -- there are no occurrences of p, x is returned. chainl :: ReadP a -> ReadP (a -> a -> a) -> a -> ReadP a -- | Like chainl, but parses one or more occurrences of p. chainl1 :: ReadP a -> ReadP (a -> a -> a) -> ReadP a -- | Like chainr, but parses one or more occurrences of p. chainr1 :: ReadP a -> ReadP (a -> a -> a) -> ReadP a -- | manyTill p end parses zero or more occurrences of p, -- until end succeeds. Returns a list of values returned by -- p. manyTill :: ReadP a -> ReadP end -> ReadP [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)] -- | Converts a parser into a Haskell ReadS-style function. This is the -- main way in which you can "run" a ReadP parser: the expanded -- type is readP_to_S :: ReadP a -> String -> [(a,String)] -- readP_to_S :: ReadP a -> ReadS a -- | Converts a Haskell ReadS-style function into a parser. Warning: This -- introduces local backtracking in the resulting parser, and therefore a -- possible inefficiency. readS_to_P :: ReadS a -> ReadP a instance GHC.Base.Functor Text.ParserCombinators.ReadP.P instance GHC.Base.Functor Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Applicative Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Monad Text.ParserCombinators.ReadP.ReadP instance Control.Monad.Fail.MonadFail Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Alternative Text.ParserCombinators.ReadP.ReadP instance GHC.Base.MonadPlus Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Applicative Text.ParserCombinators.ReadP.P instance GHC.Base.MonadPlus Text.ParserCombinators.ReadP.P instance GHC.Base.Monad Text.ParserCombinators.ReadP.P instance Control.Monad.Fail.MonadFail Text.ParserCombinators.ReadP.P instance GHC.Base.Alternative Text.ParserCombinators.ReadP.P -- | This library defines parser combinators for precedence parsing. module Text.ParserCombinators.ReadPrec data ReadPrec a type Prec = Int minPrec :: Prec -- | Lift a precedence-insensitive ReadP to a ReadPrec. lift :: ReadP a -> ReadPrec a -- | (prec n p) checks whether the precedence context is less than -- or equal to n, and -- -- prec :: Prec -> ReadPrec a -> ReadPrec a -- | Increases the precedence context by one. step :: ReadPrec a -> ReadPrec a -- | Resets the precedence context to zero. reset :: ReadPrec a -> ReadPrec a -- | Consumes and returns the next character. Fails if there is no input -- left. get :: ReadPrec Char -- | Look-ahead: returns the part of the input that is left, without -- consuming it. look :: ReadPrec String -- | Symmetric choice. (+++) :: ReadPrec a -> ReadPrec a -> ReadPrec a -- | Local, exclusive, left-biased choice: If left parser locally produces -- any result at all, then right parser is not used. (<++) :: ReadPrec a -> ReadPrec a -> ReadPrec a -- | Always fails. pfail :: ReadPrec a -- | Combines all parsers in the specified list. choice :: [ReadPrec a] -> ReadPrec a readPrec_to_P :: ReadPrec a -> (Int -> ReadP a) readP_to_Prec :: (Int -> ReadP a) -> ReadPrec a readPrec_to_S :: ReadPrec a -> (Int -> ReadS a) readS_to_Prec :: (Int -> ReadS a) -> ReadPrec a instance GHC.Base.Functor Text.ParserCombinators.ReadPrec.ReadPrec instance GHC.Base.Applicative Text.ParserCombinators.ReadPrec.ReadPrec instance GHC.Base.Monad Text.ParserCombinators.ReadPrec.ReadPrec instance Control.Monad.Fail.MonadFail Text.ParserCombinators.ReadPrec.ReadPrec instance GHC.Base.MonadPlus Text.ParserCombinators.ReadPrec.ReadPrec instance GHC.Base.Alternative Text.ParserCombinators.ReadPrec.ReadPrec -- | The cut-down Haskell lexer, used by Text.Read module Text.Read.Lex data Lexeme -- | Character literal Char :: Char -> Lexeme -- | String literal, with escapes interpreted String :: String -> Lexeme -- | Punctuation or reserved symbol, e.g. (, :: Punc :: String -> Lexeme -- | Haskell identifier, e.g. foo, Baz Ident :: String -> Lexeme -- | Haskell symbol, e.g. >>, :% Symbol :: String -> Lexeme Number :: Number -> Lexeme EOF :: Lexeme data Number numberToInteger :: Number -> Maybe Integer numberToFixed :: Integer -> Number -> Maybe (Integer, Integer) numberToRational :: Number -> Rational numberToRangedRational :: (Int, Int) -> Number -> Maybe Rational lex :: ReadP Lexeme expect :: Lexeme -> ReadP () -- | Haskell lexer: returns the lexed string, rather than the lexeme hsLex :: ReadP String lexChar :: ReadP Char readIntP :: Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadP a readOctP :: (Eq a, Num a) => ReadP a readDecP :: (Eq a, Num a) => ReadP a readHexP :: (Eq a, Num a) => ReadP a isSymbolChar :: Char -> Bool instance GHC.Show.Show Text.Read.Lex.Lexeme instance GHC.Classes.Eq Text.Read.Lex.Lexeme instance GHC.Show.Show Text.Read.Lex.Number instance GHC.Classes.Eq Text.Read.Lex.Number -- | Odds and ends, mostly functions for reading and showing -- RealFloat-like kind of values. module Numeric -- | Converts a possibly-negative Real value to a string. showSigned :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS -- | Shows a non-negative Integral number using the base -- specified by the first argument, and the character representation -- specified by the second. showIntAtBase :: (Integral a, Show a) => a -> (Int -> Char) -> a -> ShowS -- | Show non-negative Integral numbers in base 10. showInt :: Integral a => a -> ShowS -- | Show non-negative Integral numbers in base 16. showHex :: (Integral a, Show a) => a -> ShowS -- | Show non-negative Integral numbers in base 8. showOct :: (Integral a, Show a) => a -> ShowS -- | Show a signed RealFloat value using scientific (exponential) -- notation (e.g. 2.45e2, 1.5e-3). -- -- In the call showEFloat digs val, if digs is -- Nothing, the value is shown to full precision; if digs -- is Just d, then at most d digits after the -- decimal point are shown. showEFloat :: (RealFloat a) => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- (e.g. 245000, 0.0015). -- -- In the call showFFloat digs val, if digs is -- Nothing, the value is shown to full precision; if digs -- is Just d, then at most d digits after the -- decimal point are shown. showFFloat :: (RealFloat a) => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- for arguments whose absolute value lies between 0.1 and -- 9,999,999, and scientific notation otherwise. -- -- In the call showGFloat digs val, if digs is -- Nothing, the value is shown to full precision; if digs -- is Just d, then at most d digits after the -- decimal point are shown. showGFloat :: (RealFloat a) => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- (e.g. 245000, 0.0015). -- -- This behaves as showFFloat, except that a decimal point is -- always guaranteed, even if not needed. showFFloatAlt :: (RealFloat a) => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- for arguments whose absolute value lies between 0.1 and -- 9,999,999, and scientific notation otherwise. -- -- This behaves as showFFloat, except that a decimal point is -- always guaranteed, even if not needed. showGFloatAlt :: (RealFloat a) => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value to full precision using standard -- decimal notation for arguments whose absolute value lies between -- 0.1 and 9,999,999, and scientific notation -- otherwise. showFloat :: (RealFloat a) => a -> ShowS -- | floatToDigits takes a base and a non-negative RealFloat -- number, and returns a list of digits and an exponent. In particular, -- if x>=0, and -- --
--   floatToDigits base x = ([d1,d2,...,dn], e)
--   
-- -- then -- --
    --
  1. n >= 1
  2. --
  3. x = 0.d1d2...dn * (base**e)
  4. --
  5. 0 <= di <= base-1
  6. --
floatToDigits :: (RealFloat a) => Integer -> a -> ([Int], Int) -- | Reads a signed Real value, given a reader for an -- unsigned value. readSigned :: (Real a) => ReadS a -> ReadS a -- | Reads an unsigned Integral value in an arbitrary base. readInt :: Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a -- | Read an unsigned number in decimal notation. readDec :: (Eq a, Num a) => ReadS a -- | Read an unsigned number in octal notation. readOct :: (Eq a, Num a) => ReadS a -- | Read an unsigned number in hexadecimal notation. Both upper or lower -- case letters are allowed. readHex :: (Eq a, Num a) => ReadS a -- | Reads an unsigned RealFrac value, expressed in decimal -- scientific notation. readFloat :: RealFrac a => ReadS a -- | Reads a non-empty string of decimal digits. lexDigits :: ReadS String -- | Converts a Rational value into any type in class -- RealFloat. fromRat :: (RealFloat a) => Rational -> a -- | Trigonometric and hyperbolic functions and related functions. class (Fractional a) => Floating a pi :: Floating a => a exp, log, sqrt :: Floating a => a -> a exp, log, sqrt :: Floating a => a -> a exp, log, sqrt :: Floating a => a -> a (**, logBase) :: Floating a => a -> a -> a (**, logBase) :: Floating a => a -> a -> a sin, cos, tan :: Floating a => a -> a sin, cos, tan :: Floating a => a -> a sin, cos, tan :: Floating a => a -> a asin, acos, atan :: Floating a => a -> a asin, acos, atan :: Floating a => a -> a asin, acos, atan :: Floating a => a -> a sinh, cosh, tanh :: Floating a => a -> a sinh, cosh, tanh :: Floating a => a -> a sinh, cosh, tanh :: Floating a => a -> a asinh, acosh, atanh :: Floating a => a -> a asinh, acosh, atanh :: Floating a => a -> a asinh, acosh, atanh :: Floating a => a -> a -- | log1p x computes log (1 + x), but -- provides more precise results for small (absolute) values of -- x if possible. log1p :: Floating a => a -> a -- | expm1 x computes exp x - 1, but -- provides more precise results for small (absolute) values of -- x if possible. expm1 :: Floating a => a -> a -- | log1pexp x computes log (1 + exp -- x), but provides more precise results if possible. -- -- Examples: -- -- log1pexp :: Floating a => a -> a -- | log1mexp x computes log (1 - exp -- x), but provides more precise results if possible. -- -- Examples: -- -- log1mexp :: Floating a => a -> a -- | This module is part of the Foreign Function Interface (FFI) and will -- usually be imported via the module Foreign. module Foreign.StablePtr -- | A stable pointer is a reference to a Haskell expression that is -- guaranteed not to be affected by garbage collection, i.e., it will -- neither be deallocated nor will the value of the stable pointer itself -- change during garbage collection (ordinary references may be relocated -- during garbage collection). Consequently, stable pointers can be -- passed to foreign code, which can treat it as an opaque reference to a -- Haskell value. -- -- A value of type StablePtr a is a stable pointer to a Haskell -- expression of type a. data {-# CTYPE "HsStablePtr" #-} StablePtr a -- | Create a stable pointer referring to the given Haskell value. newStablePtr :: a -> IO (StablePtr a) -- | Obtain the Haskell value referenced by a stable pointer, i.e., the -- same value that was passed to the corresponding call to -- makeStablePtr. If the argument to deRefStablePtr has -- already been freed using freeStablePtr, the behaviour of -- deRefStablePtr is undefined. deRefStablePtr :: StablePtr a -> IO a -- | Dissolve the association between the stable pointer and the Haskell -- value. Afterwards, if the stable pointer is passed to -- deRefStablePtr or freeStablePtr, the behaviour is -- undefined. However, the stable pointer may still be passed to -- castStablePtrToPtr, but the Ptr () value -- returned by castStablePtrToPtr, in this case, is undefined (in -- particular, it may be nullPtr). Nevertheless, the call to -- castStablePtrToPtr is guaranteed not to diverge. freeStablePtr :: StablePtr a -> IO () -- | Coerce a stable pointer to an address. No guarantees are made about -- the resulting value, except that the original stable pointer can be -- recovered by castPtrToStablePtr. In particular, the address may -- not refer to an accessible memory location and any attempt to pass it -- to the member functions of the class Storable leads to -- undefined behaviour. castStablePtrToPtr :: StablePtr a -> Ptr () -- | The inverse of castStablePtrToPtr, i.e., we have the identity -- --
--   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 module GHC.Fingerprint.Type data Fingerprint Fingerprint :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> Fingerprint instance GHC.Classes.Ord GHC.Fingerprint.Type.Fingerprint instance GHC.Classes.Eq GHC.Fingerprint.Type.Fingerprint instance GHC.Show.Show GHC.Fingerprint.Type.Fingerprint -- | Unsigned integer types. module Data.Word -- | A Word is an unsigned integral type, with the same size as -- Int. data Word :: * -- | 8-bit unsigned integer type data {-# CTYPE "HsWord8" #-} Word8 -- | 16-bit unsigned integer type data {-# CTYPE "HsWord16" #-} Word16 -- | 32-bit unsigned integer type data {-# CTYPE "HsWord32" #-} Word32 -- | 64-bit unsigned integer type data {-# CTYPE "HsWord64" #-} Word64 -- | Swap bytes in Word16. byteSwap16 :: Word16 -> Word16 -- | Reverse order of bytes in Word32. byteSwap32 :: Word32 -> Word32 -- | Reverse order of bytes in Word64. byteSwap64 :: Word64 -> Word64 -- | 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. class Storable a -- | Computes the storage requirements (in bytes) of the argument. The -- value of the argument is not used. sizeOf :: Storable a => a -> Int -- | Computes the alignment constraint of the argument. An alignment -- constraint x is fulfilled by any address divisible by -- x. The value of the argument is not used. alignment :: Storable a => a -> Int -- | Read a value from a memory area regarded as an array of values of the -- same kind. The first argument specifies the start address of the array -- and the second the index into the array (the first element of the -- array has index 0). The following equality holds, -- --
--   peekElemOff addr idx = IOExts.fixIO $ \result ->
--     peek (addr `plusPtr` (idx * sizeOf result))
--   
-- -- Note that this is only a specification, not necessarily the concrete -- implementation of the function. peekElemOff :: Storable a => Ptr a -> Int -> IO a -- | Write a value to a memory area regarded as an array of values of the -- same kind. The following equality holds: -- --
--   pokeElemOff addr idx x = 
--     poke (addr `plusPtr` (idx * sizeOf x)) x
--   
pokeElemOff :: Storable a => Ptr a -> Int -> a -> IO () -- | Read a value from a memory location given by a base address and -- offset. The following equality holds: -- --
--   peekByteOff addr off = peek (addr `plusPtr` off)
--   
peekByteOff :: Storable a => Ptr b -> Int -> IO a -- | Write a value to a memory location given by a base address and offset. -- The following equality holds: -- --
--   pokeByteOff addr off x = poke (addr `plusPtr` off) x
--   
pokeByteOff :: Storable a => Ptr b -> Int -> a -> IO () -- | Read a value from the given memory location. -- -- Note that the peek and poke functions might require properly aligned -- addresses to function correctly. This is architecture dependent; thus, -- portable code should ensure that when peeking or poking values of some -- type a, the alignment constraint for a, as given by -- the function alignment is fulfilled. peek :: Storable a => Ptr a -> IO a -- | Write the given value to the given memory location. Alignment -- restrictions might apply; see peek. poke :: Storable a => Ptr a -> a -> IO () instance Foreign.Storable.Storable () instance Foreign.Storable.Storable GHC.Types.Bool instance Foreign.Storable.Storable GHC.Types.Char instance Foreign.Storable.Storable GHC.Types.Int instance Foreign.Storable.Storable GHC.Types.Word instance Foreign.Storable.Storable (GHC.Ptr.Ptr a) instance Foreign.Storable.Storable (GHC.Ptr.FunPtr a) instance Foreign.Storable.Storable (GHC.Stable.StablePtr a) instance Foreign.Storable.Storable GHC.Types.Float instance Foreign.Storable.Storable GHC.Types.Double instance Foreign.Storable.Storable GHC.Word.Word8 instance Foreign.Storable.Storable GHC.Word.Word16 instance Foreign.Storable.Storable GHC.Word.Word32 instance Foreign.Storable.Storable GHC.Word.Word64 instance Foreign.Storable.Storable GHC.Int.Int8 instance Foreign.Storable.Storable GHC.Int.Int16 instance Foreign.Storable.Storable GHC.Int.Int32 instance Foreign.Storable.Storable GHC.Int.Int64 instance (Foreign.Storable.Storable a, GHC.Real.Integral a) => Foreign.Storable.Storable (GHC.Real.Ratio a) instance Foreign.Storable.Storable GHC.Fingerprint.Type.Fingerprint -- | Signed integer types module Data.Int -- | 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 :: * -- | 8-bit signed integer type data {-# CTYPE "HsInt8" #-} Int8 -- | 16-bit signed integer type data {-# CTYPE "HsInt16" #-} Int16 -- | 32-bit signed integer type data {-# CTYPE "HsInt32" #-} Int32 -- | 64-bit signed integer type data {-# CTYPE "HsInt64" #-} Int64 -- | The arbitrary-precision Natural number type. -- -- Note: This is an internal GHC module with an API subject to -- change. It's recommended use the Numeric.Natural module to -- import the Natural type. module GHC.Natural -- | Type representing arbitrary-precision non-negative integers. -- -- Operations whose result would be negative throw -- (Underflow :: ArithException). data Natural -- | in [0, maxBound::Word] NatS# :: GmpLimb# -> Natural -- | in ]maxBound::Word, +inf[ -- -- Invariant: NatJ# is used iff value doesn't fit in -- NatS# constructor. NatJ# :: {-# UNPACK #-} !BigNat -> Natural -- | Test whether all internal invariants are satisfied by Natural -- value -- -- This operation is mostly useful for test-suites and/or code which -- constructs Integer values directly. isValidNatural :: Natural -> Bool naturalFromInteger :: Integer -> Natural -- | Construct Natural from Word value. wordToNatural :: Word -> Natural -- | Try downcasting Natural to Word value. Returns -- Nothing if value doesn't fit in Word. naturalToWordMaybe :: Natural -> Maybe Word -- | Natural subtraction. Returns Nothings for non-positive -- results. minusNaturalMaybe :: Natural -> Natural -> Maybe Natural -- | "powModNatural b e m" computes -- base b raised to exponent e modulo -- m. powModNatural :: Natural -> Natural -> Natural -> Natural instance GHC.Classes.Ord GHC.Natural.Natural instance GHC.Classes.Eq GHC.Natural.Natural instance GHC.Show.Show GHC.Natural.Natural instance GHC.Read.Read GHC.Natural.Natural instance GHC.Num.Num GHC.Natural.Natural instance GHC.Real.Real GHC.Natural.Natural instance GHC.Enum.Enum GHC.Natural.Natural instance GHC.Real.Integral GHC.Natural.Natural instance GHC.Arr.Ix GHC.Natural.Natural instance Data.Bits.Bits GHC.Natural.Natural -- | The arbitrary-precision Natural number type. module Numeric.Natural -- | Type representing arbitrary-precision non-negative integers. -- -- Operations whose result would be negative throw -- (Underflow :: ArithException). data Natural -- | 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 -- -- -- -- A value of type FunPtr a may be a pointer to a foreign -- function, either returned by another foreign function or imported with -- a a static address import like -- --
--   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. newtype IntPtr IntPtr :: Int -> 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. newtype WordPtr WordPtr :: Word -> WordPtr -- | casts a Ptr to a WordPtr ptrToWordPtr :: Ptr a -> WordPtr -- | casts a WordPtr to a Ptr wordPtrToPtr :: WordPtr -> Ptr a instance GHC.Show.Show Foreign.Ptr.IntPtr instance GHC.Read.Read Foreign.Ptr.IntPtr instance Data.Bits.FiniteBits Foreign.Ptr.IntPtr instance Data.Bits.Bits Foreign.Ptr.IntPtr instance GHC.Real.Integral Foreign.Ptr.IntPtr instance GHC.Enum.Bounded Foreign.Ptr.IntPtr instance GHC.Real.Real Foreign.Ptr.IntPtr instance Foreign.Storable.Storable Foreign.Ptr.IntPtr instance GHC.Enum.Enum Foreign.Ptr.IntPtr instance GHC.Num.Num Foreign.Ptr.IntPtr instance GHC.Classes.Ord Foreign.Ptr.IntPtr instance GHC.Classes.Eq Foreign.Ptr.IntPtr instance GHC.Show.Show Foreign.Ptr.WordPtr instance GHC.Read.Read Foreign.Ptr.WordPtr instance Data.Bits.FiniteBits Foreign.Ptr.WordPtr instance Data.Bits.Bits Foreign.Ptr.WordPtr instance GHC.Real.Integral Foreign.Ptr.WordPtr instance GHC.Enum.Bounded Foreign.Ptr.WordPtr instance GHC.Real.Real Foreign.Ptr.WordPtr instance Foreign.Storable.Storable Foreign.Ptr.WordPtr instance GHC.Enum.Enum Foreign.Ptr.WordPtr instance GHC.Num.Num Foreign.Ptr.WordPtr instance GHC.Classes.Ord Foreign.Ptr.WordPtr instance GHC.Classes.Eq Foreign.Ptr.WordPtr -- | 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 -- | Haskell type representing the C bool type. newtype {-# CTYPE "bool" #-} CBool CBool :: Word8 -> CBool 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 GHC.Show.Show Foreign.C.Types.CUIntMax instance GHC.Read.Read Foreign.C.Types.CUIntMax instance Data.Bits.FiniteBits Foreign.C.Types.CUIntMax instance Data.Bits.Bits Foreign.C.Types.CUIntMax instance GHC.Real.Integral Foreign.C.Types.CUIntMax instance GHC.Enum.Bounded Foreign.C.Types.CUIntMax instance GHC.Real.Real Foreign.C.Types.CUIntMax instance Foreign.Storable.Storable Foreign.C.Types.CUIntMax instance GHC.Enum.Enum Foreign.C.Types.CUIntMax instance GHC.Num.Num Foreign.C.Types.CUIntMax instance GHC.Classes.Ord Foreign.C.Types.CUIntMax instance GHC.Classes.Eq Foreign.C.Types.CUIntMax instance GHC.Show.Show Foreign.C.Types.CIntMax instance GHC.Read.Read Foreign.C.Types.CIntMax instance Data.Bits.FiniteBits Foreign.C.Types.CIntMax instance Data.Bits.Bits Foreign.C.Types.CIntMax instance GHC.Real.Integral Foreign.C.Types.CIntMax instance GHC.Enum.Bounded Foreign.C.Types.CIntMax instance GHC.Real.Real Foreign.C.Types.CIntMax instance Foreign.Storable.Storable Foreign.C.Types.CIntMax instance GHC.Enum.Enum Foreign.C.Types.CIntMax instance GHC.Num.Num Foreign.C.Types.CIntMax instance GHC.Classes.Ord Foreign.C.Types.CIntMax instance GHC.Classes.Eq Foreign.C.Types.CIntMax instance GHC.Show.Show Foreign.C.Types.CUIntPtr instance GHC.Read.Read Foreign.C.Types.CUIntPtr instance Data.Bits.FiniteBits Foreign.C.Types.CUIntPtr instance Data.Bits.Bits Foreign.C.Types.CUIntPtr instance GHC.Real.Integral Foreign.C.Types.CUIntPtr instance GHC.Enum.Bounded Foreign.C.Types.CUIntPtr instance GHC.Real.Real Foreign.C.Types.CUIntPtr instance Foreign.Storable.Storable Foreign.C.Types.CUIntPtr instance GHC.Enum.Enum Foreign.C.Types.CUIntPtr instance GHC.Num.Num Foreign.C.Types.CUIntPtr instance GHC.Classes.Ord Foreign.C.Types.CUIntPtr instance GHC.Classes.Eq Foreign.C.Types.CUIntPtr instance GHC.Show.Show Foreign.C.Types.CIntPtr instance GHC.Read.Read Foreign.C.Types.CIntPtr instance Data.Bits.FiniteBits Foreign.C.Types.CIntPtr instance Data.Bits.Bits Foreign.C.Types.CIntPtr instance GHC.Real.Integral Foreign.C.Types.CIntPtr instance GHC.Enum.Bounded Foreign.C.Types.CIntPtr instance GHC.Real.Real Foreign.C.Types.CIntPtr instance Foreign.Storable.Storable Foreign.C.Types.CIntPtr instance GHC.Enum.Enum Foreign.C.Types.CIntPtr instance GHC.Num.Num Foreign.C.Types.CIntPtr instance GHC.Classes.Ord Foreign.C.Types.CIntPtr instance GHC.Classes.Eq Foreign.C.Types.CIntPtr instance GHC.Show.Show Foreign.C.Types.CSUSeconds instance GHC.Read.Read Foreign.C.Types.CSUSeconds instance GHC.Real.Real Foreign.C.Types.CSUSeconds instance Foreign.Storable.Storable Foreign.C.Types.CSUSeconds instance GHC.Enum.Enum Foreign.C.Types.CSUSeconds instance GHC.Num.Num Foreign.C.Types.CSUSeconds instance GHC.Classes.Ord Foreign.C.Types.CSUSeconds instance GHC.Classes.Eq Foreign.C.Types.CSUSeconds instance GHC.Show.Show Foreign.C.Types.CUSeconds instance GHC.Read.Read Foreign.C.Types.CUSeconds instance GHC.Real.Real Foreign.C.Types.CUSeconds instance Foreign.Storable.Storable Foreign.C.Types.CUSeconds instance GHC.Enum.Enum Foreign.C.Types.CUSeconds instance GHC.Num.Num Foreign.C.Types.CUSeconds instance GHC.Classes.Ord Foreign.C.Types.CUSeconds instance GHC.Classes.Eq Foreign.C.Types.CUSeconds instance GHC.Show.Show Foreign.C.Types.CTime instance GHC.Read.Read Foreign.C.Types.CTime instance GHC.Real.Real Foreign.C.Types.CTime instance Foreign.Storable.Storable Foreign.C.Types.CTime instance GHC.Enum.Enum Foreign.C.Types.CTime instance GHC.Num.Num Foreign.C.Types.CTime instance GHC.Classes.Ord Foreign.C.Types.CTime instance GHC.Classes.Eq Foreign.C.Types.CTime instance GHC.Show.Show Foreign.C.Types.CClock instance GHC.Read.Read Foreign.C.Types.CClock instance GHC.Real.Real Foreign.C.Types.CClock instance Foreign.Storable.Storable Foreign.C.Types.CClock instance GHC.Enum.Enum Foreign.C.Types.CClock instance GHC.Num.Num Foreign.C.Types.CClock instance GHC.Classes.Ord Foreign.C.Types.CClock instance GHC.Classes.Eq Foreign.C.Types.CClock instance GHC.Show.Show Foreign.C.Types.CSigAtomic instance GHC.Read.Read Foreign.C.Types.CSigAtomic instance Data.Bits.FiniteBits Foreign.C.Types.CSigAtomic instance Data.Bits.Bits Foreign.C.Types.CSigAtomic instance GHC.Real.Integral Foreign.C.Types.CSigAtomic instance GHC.Enum.Bounded Foreign.C.Types.CSigAtomic instance GHC.Real.Real Foreign.C.Types.CSigAtomic instance Foreign.Storable.Storable Foreign.C.Types.CSigAtomic instance GHC.Enum.Enum Foreign.C.Types.CSigAtomic instance GHC.Num.Num Foreign.C.Types.CSigAtomic instance GHC.Classes.Ord Foreign.C.Types.CSigAtomic instance GHC.Classes.Eq Foreign.C.Types.CSigAtomic instance GHC.Show.Show Foreign.C.Types.CWchar instance GHC.Read.Read Foreign.C.Types.CWchar instance Data.Bits.FiniteBits Foreign.C.Types.CWchar instance Data.Bits.Bits Foreign.C.Types.CWchar instance GHC.Real.Integral Foreign.C.Types.CWchar instance GHC.Enum.Bounded Foreign.C.Types.CWchar instance GHC.Real.Real Foreign.C.Types.CWchar instance Foreign.Storable.Storable Foreign.C.Types.CWchar instance GHC.Enum.Enum Foreign.C.Types.CWchar instance GHC.Num.Num Foreign.C.Types.CWchar instance GHC.Classes.Ord Foreign.C.Types.CWchar instance GHC.Classes.Eq Foreign.C.Types.CWchar instance GHC.Show.Show Foreign.C.Types.CSize instance GHC.Read.Read Foreign.C.Types.CSize instance Data.Bits.FiniteBits Foreign.C.Types.CSize instance Data.Bits.Bits Foreign.C.Types.CSize instance GHC.Real.Integral Foreign.C.Types.CSize instance GHC.Enum.Bounded Foreign.C.Types.CSize instance GHC.Real.Real Foreign.C.Types.CSize instance Foreign.Storable.Storable Foreign.C.Types.CSize instance GHC.Enum.Enum Foreign.C.Types.CSize instance GHC.Num.Num Foreign.C.Types.CSize instance GHC.Classes.Ord Foreign.C.Types.CSize instance GHC.Classes.Eq Foreign.C.Types.CSize instance GHC.Show.Show Foreign.C.Types.CPtrdiff instance GHC.Read.Read Foreign.C.Types.CPtrdiff instance Data.Bits.FiniteBits Foreign.C.Types.CPtrdiff instance Data.Bits.Bits Foreign.C.Types.CPtrdiff instance GHC.Real.Integral Foreign.C.Types.CPtrdiff instance GHC.Enum.Bounded Foreign.C.Types.CPtrdiff instance GHC.Real.Real Foreign.C.Types.CPtrdiff instance Foreign.Storable.Storable Foreign.C.Types.CPtrdiff instance GHC.Enum.Enum Foreign.C.Types.CPtrdiff instance GHC.Num.Num Foreign.C.Types.CPtrdiff instance GHC.Classes.Ord Foreign.C.Types.CPtrdiff instance GHC.Classes.Eq Foreign.C.Types.CPtrdiff instance GHC.Show.Show Foreign.C.Types.CDouble instance GHC.Read.Read Foreign.C.Types.CDouble instance GHC.Float.RealFloat Foreign.C.Types.CDouble instance GHC.Real.RealFrac Foreign.C.Types.CDouble instance GHC.Float.Floating Foreign.C.Types.CDouble instance GHC.Real.Fractional Foreign.C.Types.CDouble instance GHC.Real.Real Foreign.C.Types.CDouble instance Foreign.Storable.Storable Foreign.C.Types.CDouble instance GHC.Enum.Enum Foreign.C.Types.CDouble instance GHC.Num.Num Foreign.C.Types.CDouble instance GHC.Classes.Ord Foreign.C.Types.CDouble instance GHC.Classes.Eq Foreign.C.Types.CDouble instance GHC.Show.Show Foreign.C.Types.CFloat instance GHC.Read.Read Foreign.C.Types.CFloat instance GHC.Float.RealFloat Foreign.C.Types.CFloat instance GHC.Real.RealFrac Foreign.C.Types.CFloat instance GHC.Float.Floating Foreign.C.Types.CFloat instance GHC.Real.Fractional Foreign.C.Types.CFloat instance GHC.Real.Real Foreign.C.Types.CFloat instance Foreign.Storable.Storable Foreign.C.Types.CFloat instance GHC.Enum.Enum Foreign.C.Types.CFloat instance GHC.Num.Num Foreign.C.Types.CFloat instance GHC.Classes.Ord Foreign.C.Types.CFloat instance GHC.Classes.Eq Foreign.C.Types.CFloat instance GHC.Show.Show Foreign.C.Types.CBool instance GHC.Read.Read Foreign.C.Types.CBool instance Data.Bits.FiniteBits Foreign.C.Types.CBool instance Data.Bits.Bits Foreign.C.Types.CBool instance GHC.Real.Integral Foreign.C.Types.CBool instance GHC.Enum.Bounded Foreign.C.Types.CBool instance GHC.Real.Real Foreign.C.Types.CBool instance Foreign.Storable.Storable Foreign.C.Types.CBool instance GHC.Enum.Enum Foreign.C.Types.CBool instance GHC.Num.Num Foreign.C.Types.CBool instance GHC.Classes.Ord Foreign.C.Types.CBool instance GHC.Classes.Eq Foreign.C.Types.CBool instance GHC.Show.Show Foreign.C.Types.CULLong instance GHC.Read.Read Foreign.C.Types.CULLong instance Data.Bits.FiniteBits Foreign.C.Types.CULLong instance Data.Bits.Bits Foreign.C.Types.CULLong instance GHC.Real.Integral Foreign.C.Types.CULLong instance GHC.Enum.Bounded Foreign.C.Types.CULLong instance GHC.Real.Real Foreign.C.Types.CULLong instance Foreign.Storable.Storable Foreign.C.Types.CULLong instance GHC.Enum.Enum Foreign.C.Types.CULLong instance GHC.Num.Num Foreign.C.Types.CULLong instance GHC.Classes.Ord Foreign.C.Types.CULLong instance GHC.Classes.Eq Foreign.C.Types.CULLong instance GHC.Show.Show Foreign.C.Types.CLLong instance GHC.Read.Read Foreign.C.Types.CLLong instance Data.Bits.FiniteBits Foreign.C.Types.CLLong instance Data.Bits.Bits Foreign.C.Types.CLLong instance GHC.Real.Integral Foreign.C.Types.CLLong instance GHC.Enum.Bounded Foreign.C.Types.CLLong instance GHC.Real.Real Foreign.C.Types.CLLong instance Foreign.Storable.Storable Foreign.C.Types.CLLong instance GHC.Enum.Enum Foreign.C.Types.CLLong instance GHC.Num.Num Foreign.C.Types.CLLong instance GHC.Classes.Ord Foreign.C.Types.CLLong instance GHC.Classes.Eq Foreign.C.Types.CLLong instance GHC.Show.Show Foreign.C.Types.CULong instance GHC.Read.Read Foreign.C.Types.CULong instance Data.Bits.FiniteBits Foreign.C.Types.CULong instance Data.Bits.Bits Foreign.C.Types.CULong instance GHC.Real.Integral Foreign.C.Types.CULong instance GHC.Enum.Bounded Foreign.C.Types.CULong instance GHC.Real.Real Foreign.C.Types.CULong instance Foreign.Storable.Storable Foreign.C.Types.CULong instance GHC.Enum.Enum Foreign.C.Types.CULong instance GHC.Num.Num Foreign.C.Types.CULong instance GHC.Classes.Ord Foreign.C.Types.CULong instance GHC.Classes.Eq Foreign.C.Types.CULong instance GHC.Show.Show Foreign.C.Types.CLong instance GHC.Read.Read Foreign.C.Types.CLong instance Data.Bits.FiniteBits Foreign.C.Types.CLong instance Data.Bits.Bits Foreign.C.Types.CLong instance GHC.Real.Integral Foreign.C.Types.CLong instance GHC.Enum.Bounded Foreign.C.Types.CLong instance GHC.Real.Real Foreign.C.Types.CLong instance Foreign.Storable.Storable Foreign.C.Types.CLong instance GHC.Enum.Enum Foreign.C.Types.CLong instance GHC.Num.Num Foreign.C.Types.CLong instance GHC.Classes.Ord Foreign.C.Types.CLong instance GHC.Classes.Eq Foreign.C.Types.CLong instance GHC.Show.Show Foreign.C.Types.CUInt instance GHC.Read.Read Foreign.C.Types.CUInt instance Data.Bits.FiniteBits Foreign.C.Types.CUInt instance Data.Bits.Bits Foreign.C.Types.CUInt instance GHC.Real.Integral Foreign.C.Types.CUInt instance GHC.Enum.Bounded Foreign.C.Types.CUInt instance GHC.Real.Real Foreign.C.Types.CUInt instance Foreign.Storable.Storable Foreign.C.Types.CUInt instance GHC.Enum.Enum Foreign.C.Types.CUInt instance GHC.Num.Num Foreign.C.Types.CUInt instance GHC.Classes.Ord Foreign.C.Types.CUInt instance GHC.Classes.Eq Foreign.C.Types.CUInt instance GHC.Show.Show Foreign.C.Types.CInt instance GHC.Read.Read Foreign.C.Types.CInt instance Data.Bits.FiniteBits Foreign.C.Types.CInt instance Data.Bits.Bits Foreign.C.Types.CInt instance GHC.Real.Integral Foreign.C.Types.CInt instance GHC.Enum.Bounded Foreign.C.Types.CInt instance GHC.Real.Real Foreign.C.Types.CInt instance Foreign.Storable.Storable Foreign.C.Types.CInt instance GHC.Enum.Enum Foreign.C.Types.CInt instance GHC.Num.Num Foreign.C.Types.CInt instance GHC.Classes.Ord Foreign.C.Types.CInt instance GHC.Classes.Eq Foreign.C.Types.CInt instance GHC.Show.Show Foreign.C.Types.CUShort instance GHC.Read.Read Foreign.C.Types.CUShort instance Data.Bits.FiniteBits Foreign.C.Types.CUShort instance Data.Bits.Bits Foreign.C.Types.CUShort instance GHC.Real.Integral Foreign.C.Types.CUShort instance GHC.Enum.Bounded Foreign.C.Types.CUShort instance GHC.Real.Real Foreign.C.Types.CUShort instance Foreign.Storable.Storable Foreign.C.Types.CUShort instance GHC.Enum.Enum Foreign.C.Types.CUShort instance GHC.Num.Num Foreign.C.Types.CUShort instance GHC.Classes.Ord Foreign.C.Types.CUShort instance GHC.Classes.Eq Foreign.C.Types.CUShort instance GHC.Show.Show Foreign.C.Types.CShort instance GHC.Read.Read Foreign.C.Types.CShort instance Data.Bits.FiniteBits Foreign.C.Types.CShort instance Data.Bits.Bits Foreign.C.Types.CShort instance GHC.Real.Integral Foreign.C.Types.CShort instance GHC.Enum.Bounded Foreign.C.Types.CShort instance GHC.Real.Real Foreign.C.Types.CShort instance Foreign.Storable.Storable Foreign.C.Types.CShort instance GHC.Enum.Enum Foreign.C.Types.CShort instance GHC.Num.Num Foreign.C.Types.CShort instance GHC.Classes.Ord Foreign.C.Types.CShort instance GHC.Classes.Eq Foreign.C.Types.CShort instance GHC.Show.Show Foreign.C.Types.CUChar instance GHC.Read.Read Foreign.C.Types.CUChar instance Data.Bits.FiniteBits Foreign.C.Types.CUChar instance Data.Bits.Bits Foreign.C.Types.CUChar instance GHC.Real.Integral Foreign.C.Types.CUChar instance GHC.Enum.Bounded Foreign.C.Types.CUChar instance GHC.Real.Real Foreign.C.Types.CUChar instance Foreign.Storable.Storable Foreign.C.Types.CUChar instance GHC.Enum.Enum Foreign.C.Types.CUChar instance GHC.Num.Num Foreign.C.Types.CUChar instance GHC.Classes.Ord Foreign.C.Types.CUChar instance GHC.Classes.Eq Foreign.C.Types.CUChar instance GHC.Show.Show Foreign.C.Types.CSChar instance GHC.Read.Read Foreign.C.Types.CSChar instance Data.Bits.FiniteBits Foreign.C.Types.CSChar instance Data.Bits.Bits Foreign.C.Types.CSChar instance GHC.Real.Integral Foreign.C.Types.CSChar instance GHC.Enum.Bounded Foreign.C.Types.CSChar instance GHC.Real.Real Foreign.C.Types.CSChar instance Foreign.Storable.Storable Foreign.C.Types.CSChar instance GHC.Enum.Enum Foreign.C.Types.CSChar instance GHC.Num.Num Foreign.C.Types.CSChar instance GHC.Classes.Ord Foreign.C.Types.CSChar instance GHC.Classes.Eq Foreign.C.Types.CSChar instance GHC.Show.Show Foreign.C.Types.CChar instance GHC.Read.Read Foreign.C.Types.CChar instance Data.Bits.FiniteBits Foreign.C.Types.CChar instance Data.Bits.Bits Foreign.C.Types.CChar instance GHC.Real.Integral Foreign.C.Types.CChar instance GHC.Enum.Bounded Foreign.C.Types.CChar instance GHC.Real.Real Foreign.C.Types.CChar instance Foreign.Storable.Storable Foreign.C.Types.CChar instance GHC.Enum.Enum Foreign.C.Types.CChar instance GHC.Num.Num Foreign.C.Types.CChar instance GHC.Classes.Ord Foreign.C.Types.CChar instance GHC.Classes.Eq Foreign.C.Types.CChar -- | Definition of propositional equality (:~:). Pattern-matching -- on a variable of type (a :~: b) produces a proof that a ~ -- b. module Data.Type.Equality -- | Propositional equality. If a :~: b is inhabited by some -- terminating value, then the type a is the same as the type -- b. To use this equality in practice, pattern-match on the -- a :~: b to get out the Refl constructor; in the body -- of the pattern-match, the compiler knows that a ~ b. data a (:~:) b [Refl] :: a :~: a -- | Lifted, heterogeneous equality. By lifted, we mean that it can be -- bogus (deferred type error). By heterogeneous, the two types -- a and b might have different kinds. Because -- ~~ can appear unexpectedly in error messages to users who do -- not care about the difference between heterogeneous equality -- ~~ and homogeneous equality ~, this is printed as -- ~ unless -fprint-equality-relations is set. class (~#) k0 k1 a b => (~~) k0 k1 (a :: k0) (b :: k1) -- | Kind heterogeneous propositional equality. Like '(:~:)', a :~~: -- b is inhabited by a terminating value if and only if a -- is the same type as b. data (a :: k1) (:~~:) (b :: k2) [HRefl] :: a :~~: a -- | Symmetry of equality sym :: (a :~: b) -> (b :~: a) -- | Transitivity of equality trans :: (a :~: b) -> (b :~: c) -> (a :~: c) -- | Type-safe cast, using propositional equality castWith :: (a :~: b) -> a -> b -- | Generalized form of type-safe cast using propositional equality gcastWith :: (a :~: b) -> ((a ~ b) => r) -> r -- | Apply one equality to another, respectively apply :: (f :~: g) -> (a :~: b) -> (f a :~: g b) -- | Extract equality of the arguments from an equality of applied types inner :: (f a :~: g b) -> (a :~: b) -- | Extract equality of type constructors from an equality of applied -- types outer :: (f a :~: g b) -> (f :~: g) -- | This class contains types where you can learn the equality of two -- types from information contained in terms. Typically, only -- singleton types should inhabit this class. class TestEquality f -- | Conditionally prove the equality of a and b. testEquality :: TestEquality f => f a -> f b -> Maybe (a :~: b) -- | A type family to compute Boolean equality. Instances are provided only -- for open kinds, such as * and function kinds. -- Instances are also provided for datatypes exported from base. A -- poly-kinded instance is not provided, as a recursive definition -- for algebraic kinds is generally more useful. instance forall k (a :: k) (b :: k). GHC.Classes.Eq (a Data.Type.Equality.:~: b) instance forall k (a :: k) (b :: k). GHC.Show.Show (a Data.Type.Equality.:~: b) instance forall k (a :: k) (b :: k). GHC.Classes.Ord (a Data.Type.Equality.:~: b) instance forall k (a :: k) (b :: k). a ~ b => GHC.Enum.Bounded (a Data.Type.Equality.:~: b) instance forall k2 k1 (a :: k1) (b :: k2). GHC.Classes.Eq (a Data.Type.Equality.:~~: b) instance forall k2 k1 (a :: k1) (b :: k2). GHC.Show.Show (a Data.Type.Equality.:~~: b) instance forall k2 k1 (a :: k1) (b :: k2). GHC.Classes.Ord (a Data.Type.Equality.:~~: b) instance forall k2 k1 (a :: k1) (b :: k2). (a :: k1) ~~ (b :: k2) => GHC.Enum.Bounded (a Data.Type.Equality.:~~: b) instance forall k (a :: k). Data.Type.Equality.TestEquality ((Data.Type.Equality.:~:) a) instance forall k k1 (a :: k1). Data.Type.Equality.TestEquality ((Data.Type.Equality.:~~:) a) instance forall k2 k1 (a :: k1) (b :: k2). (a :: k1) ~~ (b :: k2) => GHC.Read.Read (a Data.Type.Equality.:~~: b) instance forall k2 k1 (a :: k1) (b :: k2). (a :: k1) ~~ (b :: k2) => GHC.Enum.Enum (a Data.Type.Equality.:~~: b) instance forall k (a :: k) (b :: k). a ~ b => GHC.Read.Read (a Data.Type.Equality.:~: b) instance forall k (a :: k) (b :: k). a ~ b => GHC.Enum.Enum (a Data.Type.Equality.:~: b) instance forall k (a :: k) (b :: k). a ~ b => a ~ b -- | Definition of representational equality (Coercion). module Data.Type.Coercion -- | Representational equality. If Coercion a b is inhabited by -- some terminating value, then the type a has the same -- underlying representation as the type b. -- -- To use this equality in practice, pattern-match on the Coercion a -- b to get out the Coercible a b instance, and then use -- coerce to apply it. data Coercion a b [Coercion] :: Coercible a b => Coercion a b -- | Type-safe cast, using representational equality coerceWith :: Coercion a b -> a -> b -- | Generalized form of type-safe cast using representational equality gcoerceWith :: Coercion a b -> (Coercible a b => r) -> r -- | Symmetry of representational equality sym :: Coercion a b -> Coercion b a -- | Transitivity of representational equality trans :: Coercion a b -> Coercion b c -> Coercion a c -- | Convert propositional (nominal) equality to representational equality repr :: (a :~: b) -> Coercion a b -- | This class contains types where you can learn the equality of two -- types from information contained in terms. Typically, only -- singleton types should inhabit this class. class TestCoercion f -- | Conditionally prove the representational equality of a and -- b. testCoercion :: TestCoercion f => f a -> f b -> Maybe (Coercion a b) instance forall k (a :: k) (b :: k). GHC.Classes.Eq (Data.Type.Coercion.Coercion a b) instance forall k (a :: k) (b :: k). GHC.Show.Show (Data.Type.Coercion.Coercion a b) instance forall k (a :: k) (b :: k). GHC.Classes.Ord (Data.Type.Coercion.Coercion a b) instance forall k (a :: k) (b :: k). GHC.Types.Coercible a b => GHC.Enum.Bounded (Data.Type.Coercion.Coercion a b) instance forall k (a :: k). Data.Type.Coercion.TestCoercion ((Data.Type.Equality.:~:) a) instance forall k k1 (a :: k1). Data.Type.Coercion.TestCoercion ((Data.Type.Equality.:~~:) a) instance forall k (a :: k). Data.Type.Coercion.TestCoercion (Data.Type.Coercion.Coercion a) instance forall k (a :: k) (b :: k). GHC.Types.Coercible a b => GHC.Read.Read (Data.Type.Coercion.Coercion a b) instance forall k (a :: k) (b :: k). GHC.Types.Coercible a b => GHC.Enum.Enum (Data.Type.Coercion.Coercion a b) module Control.Category -- | A class for categories. id and (.) must form a monoid. class Category cat -- | the identity morphism id :: Category cat => cat a a -- | morphism composition (.) :: Category cat => cat b c -> cat a b -> cat a c -- | Right-to-left composition (<<<) :: Category cat => cat b c -> cat a b -> cat a c infixr 1 <<< -- | Left-to-right composition (>>>) :: Category cat => cat a b -> cat b c -> cat a c infixr 1 >>> instance Control.Category.Category (->) instance Control.Category.Category (Data.Type.Equality.:~:) instance Control.Category.Category (Data.Type.Equality.:~~:) instance Control.Category.Category Data.Type.Coercion.Coercion -- | Definition of a Proxy type (poly-kinded in GHC) module Data.Proxy -- | A concrete, poly-kinded proxy type data Proxy t Proxy :: Proxy t -- | asProxyTypeOf 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 -- tag of the second. asProxyTypeOf :: a -> proxy a -> a -- | A concrete, promotable proxy type, for use at the kind level There are -- no instances for this because it is intended at the kind level only data KProxy (t :: *) KProxy :: KProxy instance forall k (t :: k). GHC.Enum.Bounded (Data.Proxy.Proxy t) instance forall k (s :: k). GHC.Classes.Eq (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Classes.Ord (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Show.Show (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Read.Read (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Enum.Enum (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Arr.Ix (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Base.Monoid (Data.Proxy.Proxy s) instance GHC.Base.Functor Data.Proxy.Proxy instance GHC.Base.Applicative Data.Proxy.Proxy instance GHC.Base.Alternative Data.Proxy.Proxy instance GHC.Base.Monad Data.Proxy.Proxy instance GHC.Base.MonadPlus Data.Proxy.Proxy -- | 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 -- | 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 -- -- Provides Show and Read instances (since: -- 4.7.0.0). newtype Down a Down :: a -> Down a -- |
--   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 instance GHC.Read.Read a => GHC.Read.Read (Data.Ord.Down a) instance GHC.Show.Show a => GHC.Show.Show (Data.Ord.Down a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Ord.Down a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Ord.Down a) -- | 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"). -- --

Examples

-- -- The type Either String Int is the type -- of values which can be either a String or an Int. The -- Left constructor can be used only on Strings, and the -- Right constructor can be used only on Ints: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> s
--   Left "foo"
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> n
--   Right 3
--   
--   >>> :type s
--   s :: Either String Int
--   
--   >>> :type n
--   n :: Either String Int
--   
-- -- The fmap from our Functor instance will ignore -- Left values, but will apply the supplied function to values -- contained in a Right: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> fmap (*2) s
--   Left "foo"
--   
--   >>> fmap (*2) n
--   Right 6
--   
-- -- The Monad instance for Either allows us to chain -- together multiple actions which may fail, and fail overall if any of -- the individual steps failed. First we'll write a function that can -- either parse an Int from a Char, or fail. -- --
--   >>> import Data.Char ( digitToInt, isDigit )
--   
--   >>> :{
--       let parseEither :: Char -> Either String Int
--           parseEither c
--             | isDigit c = Right (digitToInt c)
--             | otherwise = Left "parse error"
--   
--   >>> :}
--   
-- -- The following should work, since both '1' and '2' -- can be parsed as Ints. -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither '1'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Right 3
--   
-- -- But the following should fail overall, since the first operation where -- we attempt to parse 'm' as an Int will fail: -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither 'm'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Left "parse error"
--   
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. -- --

Examples

-- -- We create two values of type Either String -- Int, one using the Left constructor and another -- using the Right constructor. Then we apply "either" the -- length function (if we have a String) or the -- "times-two" function (if we have an Int): -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> either length (*2) s
--   3
--   
--   >>> either length (*2) n
--   6
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> lefts list
--   ["foo","bar","baz"]
--   
lefts :: [Either a b] -> [a] -- | Extracts from a list of Either all the Right elements. -- All the Right elements are extracted in order. -- --

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> rights list
--   [3,7]
--   
rights :: [Either a b] -> [b] -- | Return True if the given value is a Left-value, -- False otherwise. -- --

Examples

-- -- Basic usage: -- --
--   >>> isLeft (Left "foo")
--   True
--   
--   >>> isLeft (Right 3)
--   False
--   
-- -- Assuming a Left value signifies some sort of error, we can use -- isLeft to write a very simple error-reporting function that -- does absolutely nothing in the case of success, and outputs "ERROR" if -- any error occurred. -- -- This example shows how isLeft might be used to avoid pattern -- matching when one does not care about the value contained in the -- constructor: -- --
--   >>> import Control.Monad ( when )
--   
--   >>> let report e = when (isLeft e) $ putStrLn "ERROR"
--   
--   >>> report (Right 1)
--   
--   >>> report (Left "parse error")
--   ERROR
--   
isLeft :: Either a b -> Bool -- | Return True if the given value is a Right-value, -- False otherwise. -- --

Examples

-- -- Basic usage: -- --
--   >>> isRight (Left "foo")
--   False
--   
--   >>> isRight (Right 3)
--   True
--   
-- -- Assuming a Left value signifies some sort of error, we can use -- isRight to write a very simple reporting function that only -- outputs "SUCCESS" when a computation has succeeded. -- -- This example shows how isRight might be used to avoid pattern -- matching when one does not care about the value contained in the -- constructor: -- --
--   >>> import Control.Monad ( when )
--   
--   >>> let report e = when (isRight e) $ putStrLn "SUCCESS"
--   
--   >>> report (Left "parse error")
--   
--   >>> report (Right 1)
--   SUCCESS
--   
isRight :: Either a b -> Bool -- | Return the contents of a Left-value or a default value -- otherwise. -- --

Examples

-- -- Basic usage: -- --
--   >>> fromLeft 1 (Left 3)
--   3
--   
--   >>> fromLeft 1 (Right "foo")
--   1
--   
fromLeft :: a -> Either a b -> a -- | Return the contents of a Right-value or a default value -- otherwise. -- --

Examples

-- -- Basic usage: -- --
--   >>> fromRight 1 (Right 3)
--   3
--   
--   >>> fromRight 1 (Left "foo")
--   1
--   
fromRight :: b -> 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. -- --

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> partitionEithers list
--   (["foo","bar","baz"],[3,7])
--   
-- -- The pair returned by partitionEithers x should be the -- same pair as (lefts x, rights x): -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> partitionEithers list == (lefts list, rights list)
--   True
--   
partitionEithers :: [Either a b] -> ([a], [b]) instance (GHC.Show.Show b, GHC.Show.Show a) => GHC.Show.Show (Data.Either.Either a b) instance (GHC.Read.Read b, GHC.Read.Read a) => GHC.Read.Read (Data.Either.Either a b) instance (GHC.Classes.Ord b, GHC.Classes.Ord a) => GHC.Classes.Ord (Data.Either.Either a b) instance (GHC.Classes.Eq b, GHC.Classes.Eq a) => GHC.Classes.Eq (Data.Either.Either a b) instance GHC.Base.Functor (Data.Either.Either a) instance GHC.Base.Applicative (Data.Either.Either e) instance GHC.Base.Monad (Data.Either.Either e) -- | 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 2010 Read. In particular, writing -- parsers is easier, and the parsers are much more efficient. module Text.Read -- | Parsing of Strings, producing values. -- -- Derived instances of Read make the following assumptions, which -- derived instances of Show obey: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Read in Haskell 2010 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
--   
-- -- Why do both readsPrec and readPrec exist, and why does -- GHC opt to implement readPrec in derived Read instances -- instead of readsPrec? The reason is that readsPrec is -- based on the ReadS type, and although ReadS is mentioned -- in the Haskell 2010 Report, it is not a very efficient parser data -- structure. -- -- readPrec, on the other hand, is based on a much more efficient -- ReadPrec datatype (a.k.a "new-style parsers"), but its -- definition relies on the use of the RankNTypes language -- extension. Therefore, readPrec (and its cousin, -- readListPrec) are marked as GHC-only. Nevertheless, it is -- recommended to use readPrec instead of readsPrec -- whenever possible for the efficiency improvements it brings. -- -- As mentioned above, derived Read instances in GHC will -- implement readPrec instead of readsPrec. The default -- implementations of readsPrec (and its cousin, readList) -- will simply use readPrec under the hood. If you are writing a -- Read instance by hand, it is recommended to write it like so: -- --
--   instance Read T where
--     readPrec     = ...
--     readListPrec = readListPrecDefault
--   
class Read a -- | attempts to parse a value from the front of the string, returning a -- list of (parsed value, remaining string) pairs. If there is no -- successful parse, the returned list is empty. -- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. readsPrec :: Read a => Int -> ReadS a -- | The method readList is provided to allow the programmer to give -- a specialised way of parsing lists of values. For example, this is -- used by the predefined Read instance of the Char type, -- where values of type String should be are expected to use -- double quotes, rather than square brackets. readList :: Read a => ReadS [a] -- | Proposed replacement for readsPrec using new-style parsers (GHC -- only). readPrec :: Read a => ReadPrec a -- | Proposed replacement for readList using new-style parsers (GHC -- only). The default definition uses readList. Instances that -- define readPrec should also define readListPrec as -- readListPrecDefault. 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: -- -- lex :: ReadS String data Lexeme -- | Character literal Char :: Char -> Lexeme -- | String literal, with escapes interpreted String :: String -> Lexeme -- | Punctuation or reserved symbol, e.g. (, :: Punc :: String -> Lexeme -- | Haskell identifier, e.g. foo, Baz Ident :: String -> Lexeme -- | Haskell symbol, e.g. >>, :% Symbol :: String -> Lexeme Number :: Number -> Lexeme EOF :: Lexeme -- | Parse a single lexeme lexP :: ReadPrec Lexeme -- | (parens p) parses "P", "(P0)", "((P0))", etc, where -- p parses "P" in the current precedence context and parses -- "P0" in precedence context zero parens :: ReadPrec a -> ReadPrec a -- | A possible replacement definition for the readList method (GHC -- only). This is only needed for GHC, and even then only for Read -- instances where readListPrec isn't defined as -- readListPrecDefault. readListDefault :: Read a => ReadS [a] -- | A possible replacement definition for the readListPrec method, -- defined using readPrec (GHC only). readListPrecDefault :: Read a => ReadPrec [a] -- | Parse a string using the Read instance. Succeeds if there is -- exactly one valid result. A Left value indicates a parse error. readEither :: Read a => String -> Either String a -- | Parse a string using the Read instance. Succeeds if there is -- exactly one valid result. readMaybe :: Read a => String -> Maybe a -- | 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. -- -- This function returns True if its argument has one of the -- following GeneralCategorys, or False otherwise: -- -- -- -- These classes are defined in the Unicode Character Database, -- part of the Unicode standard. The same document defines what is and is -- not a "Letter". -- --

Examples

-- -- Basic usage: -- --
--   >>> isLetter 'a'
--   True
--   
--   >>> isLetter 'A'
--   True
--   
--   >>> isLetter '0'
--   False
--   
--   >>> isLetter '%'
--   False
--   
--   >>> isLetter '♥'
--   False
--   
--   >>> isLetter '\31'
--   False
--   
-- -- Ensure that isLetter and isAlpha are equivalent. -- --
--   >>> let chars = [(chr 0)..]
--   
--   >>> let letters = map isLetter chars
--   
--   >>> let alphas = map isAlpha chars
--   
--   >>> letters == alphas
--   True
--   
isLetter :: Char -> Bool -- | Selects Unicode mark characters, for example accents and the like, -- which combine with preceding characters. -- -- This function returns True if its argument has one of the -- following GeneralCategorys, or False otherwise: -- -- -- -- These classes are defined in the Unicode Character Database, -- part of the Unicode standard. The same document defines what is and is -- not a "Mark". -- --

Examples

-- -- Basic usage: -- --
--   >>> isMark 'a'
--   False
--   
--   >>> isMark '0'
--   False
--   
-- -- Combining marks such as accent characters usually need to follow -- another character before they become printable: -- --
--   >>> map isMark "ò"
--   [False,True]
--   
-- -- Puns are not necessarily supported: -- --
--   >>> isMark '✓'
--   False
--   
isMark :: Char -> Bool -- | Selects Unicode numeric characters, including digits from various -- scripts, Roman numerals, et cetera. -- -- This function returns True if its argument has one of the -- following GeneralCategorys, or False otherwise: -- -- -- -- These classes are defined in the Unicode Character Database, -- part of the Unicode standard. The same document defines what is and is -- not a "Number". -- --

Examples

-- -- Basic usage: -- --
--   >>> isNumber 'a'
--   False
--   
--   >>> isNumber '%'
--   False
--   
--   >>> isNumber '3'
--   True
--   
-- -- ASCII '0' through '9' are all numbers: -- --
--   >>> and $ map isNumber ['0'..'9']
--   True
--   
-- -- Unicode Roman numerals are "numbers" as well: -- --
--   >>> isNumber 'Ⅸ'
--   True
--   
isNumber :: Char -> Bool -- | Selects Unicode punctuation characters, including various kinds of -- connectors, brackets and quotes. -- -- This function returns True if its argument has one of the -- following GeneralCategorys, or False otherwise: -- -- -- -- These classes are defined in the Unicode Character Database, -- part of the Unicode standard. The same document defines what is and is -- not a "Punctuation". -- --

Examples

-- -- Basic usage: -- --
--   >>> isPunctuation 'a'
--   False
--   
--   >>> isPunctuation '7'
--   False
--   
--   >>> isPunctuation '♥'
--   False
--   
--   >>> isPunctuation '"'
--   True
--   
--   >>> isPunctuation '?'
--   True
--   
--   >>> isPunctuation '—'
--   True
--   
isPunctuation :: Char -> Bool -- | Selects Unicode symbol characters, including mathematical and currency -- symbols. -- -- This function returns True if its argument has one of the -- following GeneralCategorys, or False otherwise: -- -- -- -- These classes are defined in the Unicode Character Database, -- part of the Unicode standard. The same document defines what is and is -- not a "Symbol". -- --

Examples

-- -- Basic usage: -- --
--   >>> isSymbol 'a'
--   False
--   
--   >>> isSymbol '6'
--   False
--   
--   >>> isSymbol '='
--   True
--   
-- -- The definition of "math symbol" may be a little counter-intuitive -- depending on one's background: -- --
--   >>> isSymbol '+'
--   True
--   
--   >>> isSymbol '-'
--   False
--   
isSymbol :: Char -> Bool -- | Selects Unicode space and separator characters. -- -- This function returns True if its argument has one of the -- following GeneralCategorys, or False otherwise: -- -- -- -- These classes are defined in the Unicode Character Database, -- part of the Unicode standard. The same document defines what is and is -- not a "Separator". -- --

Examples

-- -- Basic usage: -- --
--   >>> isSeparator 'a'
--   False
--   
--   >>> isSeparator '6'
--   False
--   
--   >>> isSeparator ' '
--   True
--   
-- -- Warning: newlines and tab characters are not considered separators. -- --
--   >>> isSeparator '\n'
--   False
--   
--   >>> isSeparator '\t'
--   False
--   
-- -- But some more exotic characters are (like HTML's &nbsp;): -- --
--   >>> isSeparator '\160'
--   True
--   
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 (the Unicode Character -- Database, in particular). -- --

Examples

-- -- Basic usage: -- --
--   >>> :t OtherLetter
--   OtherLetter :: GeneralCategory
--   
-- -- Eq instance: -- --
--   >>> UppercaseLetter == UppercaseLetter
--   True
--   
--   >>> UppercaseLetter == LowercaseLetter
--   False
--   
-- -- Ord instance: -- --
--   >>> NonSpacingMark <= MathSymbol
--   True
--   
-- -- Enum instance: -- --
--   >>> enumFromTo ModifierLetter SpacingCombiningMark
--   [ModifierLetter,OtherLetter,NonSpacingMark,SpacingCombiningMark]
--   
-- -- Read instance: -- --
--   >>> read "DashPunctuation" :: GeneralCategory
--   DashPunctuation
--   
--   >>> read "17" :: GeneralCategory
--   *** Exception: Prelude.read: no parse
--   
-- -- Show instance: -- --
--   >>> show EnclosingMark
--   "EnclosingMark"
--   
-- -- Bounded instance: -- --
--   >>> minBound :: GeneralCategory
--   UppercaseLetter
--   
--   >>> maxBound :: GeneralCategory
--   NotAssigned
--   
-- -- Ix instance: -- --
--   >>> import Data.Ix ( index )
--   
--   >>> index (OtherLetter,Control) FinalQuote
--   12
--   
--   >>> index (OtherLetter,Control) Format
--   *** Exception: Error in array index
--   
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. This relies on the -- Enum instance of GeneralCategory, which must remain in -- the same order as the categories are presented in the Unicode -- standard. -- --

Examples

-- -- Basic usage: -- --
--   >>> generalCategory 'a'
--   LowercaseLetter
--   
--   >>> generalCategory 'A'
--   UppercaseLetter
--   
--   >>> generalCategory '0'
--   DecimalNumber
--   
--   >>> generalCategory '%'
--   OtherPunctuation
--   
--   >>> generalCategory '♥'
--   OtherSymbol
--   
--   >>> generalCategory '\31'
--   Control
--   
--   >>> generalCategory ' '
--   Space
--   
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 (that is, -- '0'..'9', 'a'..'f', -- 'A'..'F'). -- --

Examples

-- -- Characters '0' through '9' are converted properly to -- 0..9: -- --
--   >>> map digitToInt ['0'..'9']
--   [0,1,2,3,4,5,6,7,8,9]
--   
-- -- Both upper- and lower-case 'A' through 'F' are -- converted as well, to 10..15. -- --
--   >>> map digitToInt ['a'..'f']
--   [10,11,12,13,14,15]
--   
--   >>> map digitToInt ['A'..'F']
--   [10,11,12,13,14,15]
--   
-- -- Anything else throws an exception: -- --
--   >>> digitToInt 'G'
--   *** Exception: Char.digitToInt: not a digit 'G'
--   
--   >>> digitToInt '♥'
--   *** Exception: Char.digitToInt: not a digit '\9829'
--   
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 -- | This legacy module provides access to the list-specialised operations -- of Data.List. This module may go away again in future GHC -- versions and is provided as transitional tool to access some of the -- list-specialised operations that had to be generalised due to the -- implementation of the Foldable/Traversable-in-Prelude Proposal -- (FTP). -- -- If the operations needed are available in GHC.List, it's -- recommended to avoid importing this module and use GHC.List -- instead for now. module GHC.OldList -- | 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] infixr 5 ++ -- | 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] -- | Decompose a list into its head and tail. If the list is empty, returns -- Nothing. If the list is non-empty, returns Just (x, -- xs), where x is the head of the list and xs its -- tail. uncons :: [a] -> Maybe (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]]
--   
-- -- If some of the rows are shorter than the following rows, their -- elements are skipped: -- --
--   transpose [[10,11],[20],[],[30,31,32]] == [[10,20,30],[11,31],[32]]
--   
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 :: forall a b. (b -> a -> b) -> b -> [a] -> b -- | A strict version of foldl. foldl' :: forall a b. (b -> a -> b) -> b -> [a] -> b -- | 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 :: (b -> a -> b) -> b -> [a] -> [b] -- | A strictly accumulating version of scanl scanl' :: (b -> a -> b) -> b -> [a] -> [b] -- | 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 (xs ++ _|_) = inits xs ++ _|_ -- -- In particular, 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. The second list 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 infix 4 `elem` -- | notElem is the negation of elem. notElem :: (Eq a) => a -> [a] -> Bool infix 4 `notElem` -- | 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 infixl 9 !! -- | 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 is right-lazy: -- --
--   zip [] _|_ = []
--   
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 is right-lazy: -- --
--   zipWith f [] _|_ = []
--   
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. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
--   lines "" == []
--   lines "\n" == [""]
--   lines "one" == ["one"]
--   lines "one\n" == ["one"]
--   lines "one\n\n" == ["one",""]
--   lines "one\ntwo" == ["one","two"]
--   lines "one\ntwo\n" == ["one","two"]
--   
-- -- Thus lines s contains at least as many elements as -- newlines in s. 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] infix 5 \\ -- | 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. If the element is found -- in both the first and the second list, the element from the first list -- will be used. 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. -- -- Elements are arranged from from lowest to highest, keeping duplicates -- in the order they appeared in the input. sort :: (Ord a) => [a] -> [a] -- | Sort a list by comparing the results of a key function applied to each -- element. sortOn f is equivalent to sortBy (comparing -- f), but has the performance advantage of only evaluating -- f once for each element in the input list. This is called the -- decorate-sort-undecorate paradigm, or Schwartzian transform. -- -- Elements are arranged from from lowest to highest, keeping duplicates -- in the order they appeared in the input. sortOn :: Ord b => (a -> b) -> [a] -> [a] -- | The insert function takes an element and a list and inserts the -- element into the list at the first position where it is 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) => [a] -> 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 -> [a] -> ([a], [a]) -- | The genericIndex function is an overloaded version of -- !!, which accepts any Integral value as the index. genericIndex :: (Integral i) => [a] -> i -> a -- | 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] -- | Converting values to readable strings: the Show class and -- associated functions. module Text.Show -- | 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. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- For example, given the declarations -- --
--   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, -- -- class Show a -- | Convert a value to a readable String. -- -- showsPrec should satisfy the law -- --
--   showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)
--   
-- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. showsPrec :: Show a => Int -> a -> ShowS -- | A specialised variant of showsPrec, using precedence context -- zero, and returning an ordinary String. show :: Show a => a -> String -- | The method showList is provided to allow the programmer to give -- a specialised way of showing lists of values. For example, this is -- used by the predefined Show instance of the Char type, -- where values of type String should be shown in double quotes, -- rather than between square brackets. showList :: Show a => [a] -> ShowS -- | equivalent to showsPrec with a precedence of 0. shows :: (Show a) => a -> ShowS -- | utility function converting a Char to a show function that -- simply prepends the character unchanged. showChar :: Char -> ShowS -- | utility function converting a String to a show function that -- simply prepends the string unchanged. showString :: String -> ShowS -- | utility function that surrounds the inner show function with -- parentheses when the Bool parameter is True. showParen :: Bool -> ShowS -> ShowS -- | Show a list (using square brackets and commas), given a function for -- showing elements. showListWith :: (a -> ShowS) -> [a] -> ShowS -- | 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). -- -- module Unsafe.Coerce unsafeCoerce :: a -> b -- | This module is an internal GHC module. It declares the constants used -- in the implementation of type-level natural numbers. The programmer -- interface for working with type-level naturals should be defined in a -- separate library. module GHC.TypeNats -- | (Kind) This is the kind of type-level natural numbers. data Nat :: * -- | This class gives the integer associated with a type-level natural. -- There are instances of the class for every concrete literal: 0, 1, 2, -- etc. class KnownNat (n :: Nat) natVal :: forall n proxy. KnownNat n => proxy n -> Natural natVal' :: forall n. KnownNat n => Proxy# n -> Natural -- | This type represents unknown type-level natural numbers. data SomeNat SomeNat :: (Proxy n) -> SomeNat -- | Convert an integer into an unknown type-level natural. someNatVal :: Natural -> SomeNat -- | We either get evidence that this function was instantiated with the -- same type-level numbers, or Nothing. sameNat :: (KnownNat a, KnownNat b) => Proxy a -> Proxy b -> Maybe (a :~: b) -- | Comparison of type-level naturals, as a constraint. type x <= y = (x <=? y) ~ 'True -- | Comparison of type-level naturals, as a function. NOTE: The -- functionality for this function should be subsumed by CmpNat, -- so this might go away in the future. Please let us know, if you -- encounter discrepancies between the two. -- | Addition of type-level naturals. -- | Multiplication of type-level naturals. -- | Exponentiation of type-level naturals. -- | Subtraction of type-level naturals. -- | Comparison of type-level naturals, as a function. instance GHC.Classes.Eq GHC.TypeNats.SomeNat instance GHC.Classes.Ord GHC.TypeNats.SomeNat instance GHC.Show.Show GHC.TypeNats.SomeNat instance GHC.Read.Read GHC.TypeNats.SomeNat -- | This module is an internal GHC module. It declares the constants used -- in the implementation of type-level natural numbers. The programmer -- interface for working with type-level naturals should be defined in a -- separate library. module GHC.TypeLits -- | (Kind) This is the kind of type-level natural numbers. data Nat :: * -- | (Kind) This is the kind of type-level symbols. Declared here because -- class IP needs it data Symbol :: * -- | This class gives the integer associated with a type-level natural. -- There are instances of the class for every concrete literal: 0, 1, 2, -- etc. class KnownNat (n :: Nat) natVal :: forall n proxy. KnownNat n => proxy n -> Integer natVal' :: forall n. KnownNat n => Proxy# n -> Integer -- | This class gives the string associated with a type-level symbol. There -- are instances of the class for every concrete literal: "hello", etc. class KnownSymbol (n :: Symbol) symbolVal :: forall n proxy. KnownSymbol n => proxy n -> String symbolVal' :: forall n. KnownSymbol n => Proxy# n -> String -- | This type represents unknown type-level natural numbers. data SomeNat SomeNat :: (Proxy n) -> SomeNat -- | This type represents unknown type-level symbols. data SomeSymbol SomeSymbol :: (Proxy n) -> SomeSymbol -- | Convert an integer into an unknown type-level natural. someNatVal :: Integer -> Maybe SomeNat -- | Convert a string into an unknown type-level symbol. someSymbolVal :: String -> SomeSymbol -- | We either get evidence that this function was instantiated with the -- same type-level numbers, or Nothing. sameNat :: (KnownNat a, KnownNat b) => Proxy a -> Proxy b -> Maybe (a :~: b) -- | We either get evidence that this function was instantiated with the -- same type-level symbols, or Nothing. sameSymbol :: (KnownSymbol a, KnownSymbol b) => Proxy a -> Proxy b -> Maybe (a :~: b) -- | Comparison of type-level naturals, as a constraint. type x <= y = (x <=? y) ~ 'True -- | Comparison of type-level naturals, as a function. NOTE: The -- functionality for this function should be subsumed by CmpNat, -- so this might go away in the future. Please let us know, if you -- encounter discrepancies between the two. -- | Addition of type-level naturals. -- | Multiplication of type-level naturals. -- | Exponentiation of type-level naturals. -- | Subtraction of type-level naturals. -- | Concatenation of type-level symbols. -- | Comparison of type-level naturals, as a function. -- | Comparison of type-level symbols, as a function. -- | The type-level equivalent of error. -- -- The polymorphic kind of this type allows it to be used in several -- settings. For instance, it can be used as a constraint, e.g. to -- provide a better error message for a non-existent instance, -- --
--   -- in a context
--   instance TypeError (Text "Cannot Show functions." :$$:
--                       Text "Perhaps there is a missing argument?")
--         => Show (a -> b) where
--       showsPrec = error "unreachable"
--   
-- -- It can also be placed on the right-hand side of a type-level function -- to provide an error for an invalid case, -- --
--   type family ByteSize x where
--      ByteSize Word16   = 2
--      ByteSize Word8    = 1
--      ByteSize a        = TypeError (Text "The type " :<>: ShowType a :<>:
--                                     Text " is not exportable.")
--   
-- | A description of a custom type error. data ErrorMessage -- | Show the text as is. Text :: Symbol -> ErrorMessage -- | Pretty print the type. ShowType :: k -> ErrorMessage ShowType :: t -> ErrorMessage -- | Put two pieces of error message next to each other. (:<>:) :: ErrorMessage -> ErrorMessage -> ErrorMessage -- | Stack two pieces of error message on top of each other. (:$$:) :: ErrorMessage -> ErrorMessage -> ErrorMessage instance GHC.Classes.Eq GHC.TypeLits.SomeSymbol instance GHC.Classes.Ord GHC.TypeLits.SomeSymbol instance GHC.Show.Show GHC.TypeLits.SomeSymbol instance GHC.Read.Read GHC.TypeLits.SomeSymbol -- | If you're using GHC.Generics, you should consider using the -- http://hackage.haskell.org/package/generic-deriving package, -- which contains many useful generic functions. module GHC.Generics -- | Void: used for datatypes without constructors data V1 (p :: k) -- | Unit: used for constructors without arguments data U1 (p :: k) U1 :: U1 -- | Used for marking occurrences of the parameter newtype Par1 p Par1 :: p -> Par1 p [unPar1] :: Par1 p -> p -- | Recursive calls of kind * -> * (or kind k -> -- *, when PolyKinds is enabled) newtype Rec1 (f :: k -> *) (p :: k) Rec1 :: f p -> Rec1 [unRec1] :: Rec1 -> f p -- | Constants, additional parameters and recursion of kind * newtype K1 (i :: *) c (p :: k) K1 :: c -> K1 c [unK1] :: K1 c -> c -- | Meta-information (constructor names, etc.) newtype M1 (i :: *) (c :: Meta) (f :: k -> *) (p :: k) M1 :: f p -> M1 [unM1] :: M1 -> f p -- | Sums: encode choice between constructors data (:+:) (f :: k -> *) (g :: k -> *) (p :: k) L1 :: (f p) -> (:+:) R1 :: (g p) -> (:+:) -- | Products: encode multiple arguments to constructors data (:*:) (f :: k -> *) (g :: k -> *) (p :: k) (:*:) :: f p -> g p -> (:*:) -- | Composition of functors newtype (:.:) (f :: k2 -> *) (g :: k1 -> k2) (p :: k1) Comp1 :: f (g p) -> (:.:) [unComp1] :: (:.:) -> f (g p) -- | Constants of unlifted kinds -- | Type synonym for URec Addr# type UAddr = URec (Ptr ()) -- | Type synonym for URec Char# type UChar = URec Char -- | Type synonym for URec Double# type UDouble = URec Double -- | Type synonym for URec Float# type UFloat = URec Float -- | Type synonym for URec Int# type UInt = URec Int -- | Type synonym for URec Word# type UWord = URec Word -- | Type synonym for encoding recursion (of kind *) type Rec0 = K1 R -- | Tag for K1: recursion (of kind *) data R -- | Type synonym for encoding meta-information for datatypes type D1 = M1 D -- | Type synonym for encoding meta-information for constructors type C1 = M1 C -- | Type synonym for encoding meta-information for record selectors type S1 = M1 S -- | Tag for M1: datatype data D -- | Tag for M1: constructor data C -- | Tag for M1: record selector data S -- | Class for datatypes that represent datatypes class Datatype d -- | The name of the datatype (unqualified) datatypeName :: Datatype d => t d (f :: k -> *) (a :: k) -> [Char] -- | The fully-qualified name of the module where the type is declared moduleName :: Datatype d => t d (f :: k -> *) (a :: k) -> [Char] -- | The package name of the module where the type is declared packageName :: Datatype d => t d (f :: k -> *) (a :: k) -> [Char] -- | Marks if the datatype is actually a newtype isNewtype :: Datatype d => t d (f :: k -> *) (a :: k) -> Bool -- | Class for datatypes that represent data constructors class Constructor c -- | The name of the constructor conName :: Constructor c => t c (f :: k -> *) (a :: k) -> [Char] -- | The fixity of the constructor conFixity :: Constructor c => t c (f :: k -> *) (a :: k) -> Fixity -- | Marks if this constructor is a record conIsRecord :: Constructor c => t c (f :: k -> *) (a :: k) -> Bool -- | Class for datatypes that represent records class Selector s -- | The name of the selector selName :: Selector s => t s (f :: k -> *) (a :: k) -> [Char] -- | The selector's unpackedness annotation (if any) selSourceUnpackedness :: Selector s => t s (f :: k -> *) (a :: k) -> SourceUnpackedness -- | The selector's strictness annotation (if any) selSourceStrictness :: Selector s => t s (f :: k -> *) (a :: k) -> SourceStrictness -- | The strictness that the compiler inferred for the selector selDecidedStrictness :: Selector s => t s (f :: k -> *) (a :: k) -> DecidedStrictness -- | Datatype to represent the fixity of a constructor. An infix | -- declaration directly corresponds to an application of Infix. data Fixity Prefix :: Fixity Infix :: Associativity -> Int -> Fixity -- | This variant of Fixity appears at the type level. data FixityI PrefixI :: FixityI InfixI :: Associativity -> Nat -> FixityI -- | Datatype to represent the associativity of a constructor data Associativity LeftAssociative :: Associativity RightAssociative :: Associativity NotAssociative :: Associativity -- | Get the precedence of a fixity value. prec :: Fixity -> Int -- | The unpackedness of a field as the user wrote it in the source code. -- For example, in the following data type: -- --
--   data E = ExampleConstructor     Int
--              {-# NOUNPACK #-} Int
--              {-#   UNPACK #-} Int
--   
-- -- The fields of ExampleConstructor have -- NoSourceUnpackedness, SourceNoUnpack, and -- SourceUnpack, respectively. data SourceUnpackedness NoSourceUnpackedness :: SourceUnpackedness SourceNoUnpack :: SourceUnpackedness SourceUnpack :: SourceUnpackedness -- | The strictness of a field as the user wrote it in the source code. For -- example, in the following data type: -- --
--   data E = ExampleConstructor Int ~Int !Int
--   
-- -- The fields of ExampleConstructor have -- NoSourceStrictness, SourceLazy, and SourceStrict, -- respectively. data SourceStrictness NoSourceStrictness :: SourceStrictness SourceLazy :: SourceStrictness SourceStrict :: SourceStrictness -- | The strictness that GHC infers for a field during compilation. Whereas -- there are nine different combinations of SourceUnpackedness and -- SourceStrictness, the strictness that GHC decides will -- ultimately be one of lazy, strict, or unpacked. What GHC decides is -- affected both by what the user writes in the source code and by GHC -- flags. As an example, consider this data type: -- --
--   data E = ExampleConstructor {-# UNPACK #-} !Int !Int Int
--   
-- -- data DecidedStrictness DecidedLazy :: DecidedStrictness DecidedStrict :: DecidedStrictness DecidedUnpack :: DecidedStrictness -- | Datatype to represent metadata associated with a datatype -- (MetaData), constructor (MetaCons), or field -- selector (MetaSel). -- -- data Meta MetaData :: Symbol -> Symbol -> Symbol -> Bool -> Meta MetaCons :: Symbol -> FixityI -> Bool -> Meta MetaSel :: (Maybe Symbol) -> SourceUnpackedness -> SourceStrictness -> DecidedStrictness -> Meta -- | Representable types of kind *. This class is derivable in GHC with the -- DeriveGeneric flag on. class Generic a where { type family Rep a :: * -> *; } -- | Convert from the datatype to its representation from :: Generic a => a -> (Rep a) x -- | Convert from the representation to the datatype to :: Generic a => (Rep a) x -> a -- | Representable types of kind * -> * (or kind k -> -- *, when PolyKinds is enabled). This class is derivable -- in GHC with the DeriveGeneric flag on. class Generic1 (f :: k -> *) where { type family Rep1 f :: k -> *; } -- | Convert from the datatype to its representation from1 :: Generic1 f => f a -> (Rep1 f) a -- | Convert from the representation to the datatype to1 :: Generic1 f => (Rep1 f) a -> f a instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *). GHC.Generics.Generic1 (GHC.Generics.M1 i c f) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Generics.Generic (GHC.Generics.M1 i c f p) instance GHC.Base.Functor f => GHC.Base.Functor (GHC.Generics.M1 i c f) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Show.Show (f p) => GHC.Show.Show (GHC.Generics.M1 i c f p) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Read.Read (f p) => GHC.Read.Read (GHC.Generics.M1 i c f p) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Classes.Ord (f p) => GHC.Classes.Ord (GHC.Generics.M1 i c f p) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Classes.Eq (f p) => GHC.Classes.Eq (GHC.Generics.M1 i c f p) instance GHC.Generics.Generic1 GHC.Generics.V1 instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.V1 p) instance GHC.Base.Functor GHC.Generics.V1 instance GHC.Generics.Generic1 GHC.Generics.U1 instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.U1 p) instance GHC.Generics.Generic1 GHC.Generics.Par1 instance GHC.Generics.Generic (GHC.Generics.Par1 p) instance GHC.Base.Functor GHC.Generics.Par1 instance GHC.Show.Show p => GHC.Show.Show (GHC.Generics.Par1 p) instance GHC.Read.Read p => GHC.Read.Read (GHC.Generics.Par1 p) instance GHC.Classes.Ord p => GHC.Classes.Ord (GHC.Generics.Par1 p) instance GHC.Classes.Eq p => GHC.Classes.Eq (GHC.Generics.Par1 p) instance forall k (f :: k -> *). GHC.Generics.Generic1 (GHC.Generics.Rec1 f) instance forall k (f :: k -> *) (p :: k). GHC.Generics.Generic (GHC.Generics.Rec1 f p) instance GHC.Base.Functor f => GHC.Base.Functor (GHC.Generics.Rec1 f) instance forall k (f :: k -> *) (p :: k). GHC.Show.Show (f p) => GHC.Show.Show (GHC.Generics.Rec1 f p) instance forall k (f :: k -> *) (p :: k). GHC.Read.Read (f p) => GHC.Read.Read (GHC.Generics.Rec1 f p) instance forall k (f :: k -> *) (p :: k). GHC.Classes.Ord (f p) => GHC.Classes.Ord (GHC.Generics.Rec1 f p) instance forall k (f :: k -> *) (p :: k). GHC.Classes.Eq (f p) => GHC.Classes.Eq (GHC.Generics.Rec1 f p) instance GHC.Generics.Generic1 (GHC.Generics.K1 i c) instance forall i c k (p :: k). GHC.Generics.Generic (GHC.Generics.K1 i c p) instance GHC.Base.Functor (GHC.Generics.K1 i c) instance forall i c k (p :: k). GHC.Show.Show c => GHC.Show.Show (GHC.Generics.K1 i c p) instance forall i c k (p :: k). GHC.Read.Read c => GHC.Read.Read (GHC.Generics.K1 i c p) instance forall i c k (p :: k). GHC.Classes.Ord c => GHC.Classes.Ord (GHC.Generics.K1 i c p) instance forall i c k (p :: k). GHC.Classes.Eq c => GHC.Classes.Eq (GHC.Generics.K1 i c p) instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (f GHC.Generics.:+: g) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). GHC.Generics.Generic ((GHC.Generics.:+:) f g p) instance (GHC.Base.Functor g, GHC.Base.Functor f) => GHC.Base.Functor (f GHC.Generics.:+: g) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Show.Show (g p), GHC.Show.Show (f p)) => GHC.Show.Show ((GHC.Generics.:+:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Read.Read (g p), GHC.Read.Read (f p)) => GHC.Read.Read ((GHC.Generics.:+:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Classes.Ord (g p), GHC.Classes.Ord (f p)) => GHC.Classes.Ord ((GHC.Generics.:+:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Classes.Eq (g p), GHC.Classes.Eq (f p)) => GHC.Classes.Eq ((GHC.Generics.:+:) f g p) instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (f GHC.Generics.:*: g) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). GHC.Generics.Generic ((GHC.Generics.:*:) f g p) instance (GHC.Base.Functor g, GHC.Base.Functor f) => GHC.Base.Functor (f GHC.Generics.:*: g) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Show.Show (g p), GHC.Show.Show (f p)) => GHC.Show.Show ((GHC.Generics.:*:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Read.Read (g p), GHC.Read.Read (f p)) => GHC.Read.Read ((GHC.Generics.:*:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Classes.Ord (g p), GHC.Classes.Ord (f p)) => GHC.Classes.Ord ((GHC.Generics.:*:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Classes.Eq (g p), GHC.Classes.Eq (f p)) => GHC.Classes.Eq ((GHC.Generics.:*:) f g p) instance forall (f :: * -> *) k (g :: k -> *). GHC.Base.Functor f => GHC.Generics.Generic1 (f GHC.Generics.:.: g) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Generics.Generic ((GHC.Generics.:.:) f g p) instance (GHC.Base.Functor g, GHC.Base.Functor f) => GHC.Base.Functor (f GHC.Generics.:.: g) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Show.Show (f (g p)) => GHC.Show.Show ((GHC.Generics.:.:) f g p) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Read.Read (f (g p)) => GHC.Read.Read ((GHC.Generics.:.:) f g p) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Classes.Ord (f (g p)) => GHC.Classes.Ord ((GHC.Generics.:.:) f g p) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Classes.Eq (f (g p)) => GHC.Classes.Eq ((GHC.Generics.:.:) f g p) instance GHC.Generics.Generic GHC.Generics.Fixity instance GHC.Read.Read GHC.Generics.Fixity instance GHC.Classes.Ord GHC.Generics.Fixity instance GHC.Show.Show GHC.Generics.Fixity instance GHC.Classes.Eq GHC.Generics.Fixity instance GHC.Generics.Generic GHC.Generics.Associativity instance GHC.Arr.Ix GHC.Generics.Associativity instance GHC.Enum.Bounded GHC.Generics.Associativity instance GHC.Enum.Enum GHC.Generics.Associativity instance GHC.Read.Read GHC.Generics.Associativity instance GHC.Classes.Ord GHC.Generics.Associativity instance GHC.Show.Show GHC.Generics.Associativity instance GHC.Classes.Eq GHC.Generics.Associativity instance GHC.Generics.Generic GHC.Generics.SourceUnpackedness instance GHC.Arr.Ix GHC.Generics.SourceUnpackedness instance GHC.Enum.Bounded GHC.Generics.SourceUnpackedness instance GHC.Enum.Enum GHC.Generics.SourceUnpackedness instance GHC.Read.Read GHC.Generics.SourceUnpackedness instance GHC.Classes.Ord GHC.Generics.SourceUnpackedness instance GHC.Show.Show GHC.Generics.SourceUnpackedness instance GHC.Classes.Eq GHC.Generics.SourceUnpackedness instance GHC.Generics.Generic GHC.Generics.SourceStrictness instance GHC.Arr.Ix GHC.Generics.SourceStrictness instance GHC.Enum.Bounded GHC.Generics.SourceStrictness instance GHC.Enum.Enum GHC.Generics.SourceStrictness instance GHC.Read.Read GHC.Generics.SourceStrictness instance GHC.Classes.Ord GHC.Generics.SourceStrictness instance GHC.Show.Show GHC.Generics.SourceStrictness instance GHC.Classes.Eq GHC.Generics.SourceStrictness instance GHC.Generics.Generic GHC.Generics.DecidedStrictness instance GHC.Arr.Ix GHC.Generics.DecidedStrictness instance GHC.Enum.Bounded GHC.Generics.DecidedStrictness instance GHC.Enum.Enum GHC.Generics.DecidedStrictness instance GHC.Read.Read GHC.Generics.DecidedStrictness instance GHC.Classes.Ord GHC.Generics.DecidedStrictness instance GHC.Show.Show GHC.Generics.DecidedStrictness instance GHC.Classes.Eq GHC.Generics.DecidedStrictness instance GHC.Generics.Generic1 (GHC.Generics.URec (GHC.Ptr.Ptr ())) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec (GHC.Ptr.Ptr ()) p) instance GHC.Base.Functor (GHC.Generics.URec (GHC.Ptr.Ptr ())) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec (GHC.Ptr.Ptr ()) p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec (GHC.Ptr.Ptr ()) p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Char) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Char p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Char) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Char p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Char p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Char p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Double) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Double p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Double) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Double p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Double p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Double p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Float) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Float p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Float) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Float p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Float p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Float p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Int) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Int p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Int) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Int p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Int p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Int p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Word) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Word p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Word) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Word p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Word p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Word p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.V1 p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.V1 p) instance forall k (p :: k). GHC.Read.Read (GHC.Generics.V1 p) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.V1 p) instance GHC.Base.Applicative f => GHC.Base.Applicative (GHC.Generics.Rec1 f) instance GHC.Base.Alternative f => GHC.Base.Alternative (GHC.Generics.Rec1 f) instance GHC.Base.MonadPlus f => GHC.Base.MonadPlus (GHC.Generics.Rec1 f) instance GHC.Base.Applicative f => GHC.Base.Applicative (GHC.Generics.M1 i c f) instance GHC.Base.Alternative f => GHC.Base.Alternative (GHC.Generics.M1 i c f) instance GHC.Base.Monad f => GHC.Base.Monad (GHC.Generics.M1 i c f) instance GHC.Base.MonadPlus f => GHC.Base.MonadPlus (GHC.Generics.M1 i c f) instance GHC.Generics.Generic [a] instance GHC.Generics.Generic (GHC.Base.Maybe a) instance GHC.Generics.Generic (Data.Either.Either a b) instance GHC.Generics.Generic GHC.Types.Bool instance GHC.Generics.Generic GHC.Types.Ordering instance forall k (t :: k). GHC.Generics.Generic (Data.Proxy.Proxy t) instance GHC.Generics.Generic () instance GHC.Generics.Generic (a, b) instance GHC.Generics.Generic (a, b, c) instance GHC.Generics.Generic (a, b, c, d) instance GHC.Generics.Generic (a, b, c, d, e) instance GHC.Generics.Generic (a, b, c, d, e, f) instance GHC.Generics.Generic (a, b, c, d, e, f, g) instance GHC.Generics.Generic1 [] instance GHC.Generics.Generic1 GHC.Base.Maybe instance GHC.Generics.Generic1 (Data.Either.Either a) instance GHC.Generics.Generic1 Data.Proxy.Proxy instance GHC.Generics.Generic1 ((,) a) instance GHC.Generics.Generic1 ((,,) a b) instance GHC.Generics.Generic1 ((,,,) a b c) instance GHC.Generics.Generic1 ((,,,,) a b c d) instance GHC.Generics.Generic1 ((,,,,,) a b c d e) instance GHC.Generics.Generic1 ((,,,,,,) a b c d e f) instance (GHC.TypeLits.KnownSymbol n, GHC.TypeLits.KnownSymbol m, GHC.TypeLits.KnownSymbol p, GHC.Generics.SingI nt) => GHC.Generics.Datatype ('GHC.Generics.MetaData n m p nt) instance (GHC.TypeLits.KnownSymbol n, GHC.Generics.SingI f, GHC.Generics.SingI r) => GHC.Generics.Constructor ('GHC.Generics.MetaCons n f r) instance (GHC.Generics.SingI mn, GHC.Generics.SingI su, GHC.Generics.SingI ss, GHC.Generics.SingI ds) => GHC.Generics.Selector ('GHC.Generics.MetaSel mn su ss ds) instance GHC.Generics.SingKind GHC.Types.Symbol instance GHC.Generics.SingKind GHC.Types.Bool instance GHC.Generics.SingKind a => GHC.Generics.SingKind (GHC.Base.Maybe a) instance GHC.Generics.SingKind GHC.Generics.FixityI instance GHC.Generics.SingKind GHC.Generics.Associativity instance GHC.Generics.SingKind GHC.Generics.SourceUnpackedness instance GHC.Generics.SingKind GHC.Generics.SourceStrictness instance GHC.Generics.SingKind GHC.Generics.DecidedStrictness instance GHC.TypeLits.KnownSymbol a => GHC.Generics.SingI a instance GHC.Generics.SingI 'GHC.Types.True instance GHC.Generics.SingI 'GHC.Types.False instance GHC.Generics.SingI 'GHC.Base.Nothing instance forall a1 (a2 :: a1). GHC.Generics.SingI a2 => GHC.Generics.SingI ('GHC.Base.Just a2) instance GHC.Generics.SingI 'GHC.Generics.PrefixI instance (GHC.Generics.SingI a, GHC.TypeNats.KnownNat n) => GHC.Generics.SingI ('GHC.Generics.InfixI a n) instance GHC.Generics.SingI 'GHC.Generics.LeftAssociative instance GHC.Generics.SingI 'GHC.Generics.RightAssociative instance GHC.Generics.SingI 'GHC.Generics.NotAssociative instance GHC.Generics.SingI 'GHC.Generics.NoSourceUnpackedness instance GHC.Generics.SingI 'GHC.Generics.SourceNoUnpack instance GHC.Generics.SingI 'GHC.Generics.SourceUnpack instance GHC.Generics.SingI 'GHC.Generics.NoSourceStrictness instance GHC.Generics.SingI 'GHC.Generics.SourceLazy instance GHC.Generics.SingI 'GHC.Generics.SourceStrict instance GHC.Generics.SingI 'GHC.Generics.DecidedLazy instance GHC.Generics.SingI 'GHC.Generics.DecidedStrict instance GHC.Generics.SingI 'GHC.Generics.DecidedUnpack instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Read.Read (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.U1 p) instance GHC.Base.Functor GHC.Generics.U1 instance GHC.Base.Applicative GHC.Generics.U1 instance GHC.Base.Alternative GHC.Generics.U1 instance GHC.Base.Monad GHC.Generics.U1 instance GHC.Base.MonadPlus GHC.Generics.U1 instance GHC.Base.Applicative GHC.Generics.Par1 instance GHC.Base.Monad GHC.Generics.Par1 instance GHC.Base.Monad f => GHC.Base.Monad (GHC.Generics.Rec1 f) instance (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (f GHC.Generics.:*: g) instance (GHC.Base.Alternative f, GHC.Base.Alternative g) => GHC.Base.Alternative (f GHC.Generics.:*: g) instance (GHC.Base.Monad f, GHC.Base.Monad g) => GHC.Base.Monad (f GHC.Generics.:*: g) instance (GHC.Base.MonadPlus f, GHC.Base.MonadPlus g) => GHC.Base.MonadPlus (f GHC.Generics.:*: g) instance (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (f GHC.Generics.:.: g) instance (GHC.Base.Alternative f, GHC.Base.Applicative g) => GHC.Base.Alternative (f GHC.Generics.:.: g) -- | 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: -- -- -- -- The method names refer to the monoid of lists under concatenation, but -- there are many other instances. -- -- Some types can be viewed as a monoid in more than one way, e.g. both -- addition and multiplication on numbers. In such cases we often define -- newtypes and make those instances of Monoid, e.g. -- Sum and Product. class Monoid a -- | Identity of mappend mempty :: Monoid a => a -- | An associative operation mappend :: Monoid a => a -> a -> a -- | Fold a list using the monoid. For most types, the default definition -- for mconcat will be used, but the function is included in the -- class definition so that an optimized version can be provided for -- specific types. mconcat :: Monoid a => [a] -> a -- | An infix synonym for mappend. (<>) :: Monoid m => m -> m -> m infixr 6 <> -- | The dual of a Monoid, obtained by swapping the arguments of -- mappend. newtype Dual a Dual :: a -> Dual a [getDual] :: Dual a -> a -- | The monoid of endomorphisms under composition. newtype Endo a Endo :: (a -> a) -> Endo a [appEndo] :: Endo a -> a -> a -- | Boolean monoid under conjunction (&&). newtype All All :: Bool -> All [getAll] :: All -> Bool -- | Boolean monoid under disjunction (||). newtype Any Any :: Bool -> Any [getAny] :: Any -> Bool -- | Monoid under addition. newtype Sum a Sum :: a -> Sum a [getSum] :: Sum a -> a -- | Monoid under multiplication. newtype Product a Product :: a -> Product a [getProduct] :: Product a -> a -- | Maybe monoid returning the leftmost non-Nothing value. -- -- First a is isomorphic to Alt Maybe -- a, but precedes it historically. newtype First a First :: Maybe a -> First a [getFirst] :: First a -> Maybe a -- | Maybe monoid returning the rightmost non-Nothing value. -- -- Last a is isomorphic to Dual (First -- a), and thus to Dual (Alt Maybe a) newtype Last a Last :: Maybe a -> Last a [getLast] :: Last a -> Maybe a -- | Monoid under <|>. newtype Alt f a Alt :: f a -> Alt f a [getAlt] :: Alt f a -> f a instance GHC.Base.Functor f => GHC.Base.Functor (Data.Monoid.Alt f) instance GHC.Base.Alternative f => GHC.Base.Alternative (Data.Monoid.Alt f) instance GHC.Base.Applicative f => GHC.Base.Applicative (Data.Monoid.Alt f) instance GHC.Base.MonadPlus f => GHC.Base.MonadPlus (Data.Monoid.Alt f) instance GHC.Base.Monad f => GHC.Base.Monad (Data.Monoid.Alt f) instance forall k (f :: k -> *) (a :: k). GHC.Enum.Enum (f a) => GHC.Enum.Enum (Data.Monoid.Alt f a) instance forall k (f :: k -> *) (a :: k). GHC.Num.Num (f a) => GHC.Num.Num (Data.Monoid.Alt f a) instance forall k (f :: k -> *) (a :: k). GHC.Classes.Ord (f a) => GHC.Classes.Ord (Data.Monoid.Alt f a) instance forall k (f :: k -> *) (a :: k). GHC.Classes.Eq (f a) => GHC.Classes.Eq (Data.Monoid.Alt f a) instance forall k (f :: k -> *) (a :: k). GHC.Show.Show (f a) => GHC.Show.Show (Data.Monoid.Alt f a) instance forall k (f :: k -> *) (a :: k). GHC.Read.Read (f a) => GHC.Read.Read (Data.Monoid.Alt f a) instance forall k (f :: k -> *). GHC.Generics.Generic1 (Data.Monoid.Alt f) instance forall k (f :: k -> *) (a :: k). GHC.Generics.Generic (Data.Monoid.Alt f a) instance GHC.Base.Monad Data.Monoid.Last instance GHC.Base.Applicative Data.Monoid.Last instance GHC.Base.Functor Data.Monoid.Last instance GHC.Generics.Generic1 Data.Monoid.Last instance GHC.Generics.Generic (Data.Monoid.Last a) instance GHC.Show.Show a => GHC.Show.Show (Data.Monoid.Last a) instance GHC.Read.Read a => GHC.Read.Read (Data.Monoid.Last a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Monoid.Last a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Monoid.Last a) instance GHC.Base.Monad Data.Monoid.First instance GHC.Base.Applicative Data.Monoid.First instance GHC.Base.Functor Data.Monoid.First instance GHC.Generics.Generic1 Data.Monoid.First instance GHC.Generics.Generic (Data.Monoid.First a) instance GHC.Show.Show a => GHC.Show.Show (Data.Monoid.First a) instance GHC.Read.Read a => GHC.Read.Read (Data.Monoid.First a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Monoid.First a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Monoid.First a) instance GHC.Num.Num a => GHC.Num.Num (Data.Monoid.Product a) instance GHC.Generics.Generic1 Data.Monoid.Product instance GHC.Generics.Generic (Data.Monoid.Product a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Monoid.Product a) instance GHC.Show.Show a => GHC.Show.Show (Data.Monoid.Product a) instance GHC.Read.Read a => GHC.Read.Read (Data.Monoid.Product a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Monoid.Product a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Monoid.Product a) instance GHC.Num.Num a => GHC.Num.Num (Data.Monoid.Sum a) instance GHC.Generics.Generic1 Data.Monoid.Sum instance GHC.Generics.Generic (Data.Monoid.Sum a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Monoid.Sum a) instance GHC.Show.Show a => GHC.Show.Show (Data.Monoid.Sum a) instance GHC.Read.Read a => GHC.Read.Read (Data.Monoid.Sum a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Monoid.Sum a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Monoid.Sum a) instance GHC.Generics.Generic Data.Monoid.Any instance GHC.Enum.Bounded Data.Monoid.Any instance GHC.Show.Show Data.Monoid.Any instance GHC.Read.Read Data.Monoid.Any instance GHC.Classes.Ord Data.Monoid.Any instance GHC.Classes.Eq Data.Monoid.Any instance GHC.Generics.Generic Data.Monoid.All instance GHC.Enum.Bounded Data.Monoid.All instance GHC.Show.Show Data.Monoid.All instance GHC.Read.Read Data.Monoid.All instance GHC.Classes.Ord Data.Monoid.All instance GHC.Classes.Eq Data.Monoid.All instance GHC.Generics.Generic (Data.Monoid.Endo a) instance GHC.Generics.Generic1 Data.Monoid.Dual instance GHC.Generics.Generic (Data.Monoid.Dual a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Monoid.Dual a) instance GHC.Show.Show a => GHC.Show.Show (Data.Monoid.Dual a) instance GHC.Read.Read a => GHC.Read.Read (Data.Monoid.Dual a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Monoid.Dual a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Monoid.Dual a) instance GHC.Base.Alternative f => GHC.Base.Monoid (Data.Monoid.Alt f a) instance GHC.Base.Monoid (Data.Monoid.Last a) instance GHC.Base.Monoid (Data.Monoid.First a) instance GHC.Num.Num a => GHC.Base.Monoid (Data.Monoid.Product a) instance GHC.Base.Functor Data.Monoid.Product instance GHC.Base.Applicative Data.Monoid.Product instance GHC.Base.Monad Data.Monoid.Product instance GHC.Num.Num a => GHC.Base.Monoid (Data.Monoid.Sum a) instance GHC.Base.Functor Data.Monoid.Sum instance GHC.Base.Applicative Data.Monoid.Sum instance GHC.Base.Monad Data.Monoid.Sum instance GHC.Base.Monoid Data.Monoid.Any instance GHC.Base.Monoid Data.Monoid.All instance GHC.Base.Monoid (Data.Monoid.Endo a) instance GHC.Base.Monoid a => GHC.Base.Monoid (Data.Monoid.Dual a) instance GHC.Base.Functor Data.Monoid.Dual instance GHC.Base.Applicative Data.Monoid.Dual instance GHC.Base.Monad Data.Monoid.Dual -- | Class of data structures that can be folded to a summary value. module Data.Foldable -- | Data structures that can be folded. -- -- 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
--   
-- -- Foldable instances are expected to satisfy the following -- laws: -- --
--   foldr f z t = appEndo (foldMap (Endo . f) t ) z
--   
-- --
--   foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
--   
-- --
--   fold = foldMap id
--   
-- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
--   sum = getSum . foldMap Sum
--   
-- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
--   foldMap f = fold . fmap f
--   
-- -- which implies that -- --
--   foldMap f . fmap g = foldMap (f . g)
--   
class Foldable t -- | Combine the elements of a structure using a monoid. fold :: (Foldable t, Monoid m) => t m -> m -- | Map each element of the structure to a monoid, and combine the -- results. foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | Right-associative fold of a structure. -- -- In the case of lists, foldr, when 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)...)
--   
-- -- Note that, since the head of the resulting expression is produced by -- an application of the operator to the first element of the list, -- foldr can produce a terminating expression from an infinite -- list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldr f z = foldr f z . toList
--   
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Right-associative fold of a structure, but with strict application of -- the operator. foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Left-associative fold of a structure. -- -- In the case of lists, foldl, when 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
--   
-- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldl' -- will diverge if given an infinite list. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is -- that latter does not force the "inner" results (e.g. z f -- x1 in the above example) before applying them to the operator -- (e.g. to (f x2)). This results in a thunk chain -- O(n) elements long, which then must be evaluated from the -- outside-in. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldl f z = foldl f z . toList
--   
foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | Left-associative fold of a structure but with strict application of -- the operator. -- -- This ensures that each step of the fold is forced to weak head normal -- form before being applied, avoiding the collection of thunks that -- would otherwise occur. This is often what you want to strictly reduce -- a finite list to a single, monolithic result (e.g. length). -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldl f z = foldl' f z . toList
--   
foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | A variant of foldr that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldr1 f = foldr1 f . toList
--   
foldr1 :: Foldable t => (a -> a -> a) -> t a -> a -- | A variant of foldl that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldl1 f = foldl1 f . toList
--   
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a -- | List of elements of a structure, from left to right. toList :: Foldable t => t a -> [a] -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. length :: Foldable t => t a -> Int -- | Does the element occur in the structure? elem :: (Foldable t, Eq a) => a -> t a -> Bool -- | The largest element of a non-empty structure. maximum :: forall a. (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure. minimum :: forall a. (Foldable t, Ord a) => t a -> a -- | 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 -- | 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) => (b -> a -> m b) -> b -> t a -> m b -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and ignore the results. For a version that doesn't -- ignore the results see traverse. traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () -- | for_ is traverse_ with its arguments flipped. For a -- version that doesn't ignore the results see for. -- --
--   >>> for_ [1..4] print
--   1
--   2
--   3
--   4
--   
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. For a version that doesn't ignore the results see -- sequenceA. 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. For a version that -- doesn't ignore the results see mapM. -- -- As of base 4.8.0.0, mapM_ is just traverse_, specialized -- to Monad. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () -- | forM_ is mapM_ with its arguments flipped. For a version -- that doesn't ignore the results see forM. -- -- As of base 4.8.0.0, forM_ is just for_, specialized to -- Monad. 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. For a version that doesn't ignore the results see -- sequence. -- -- As of base 4.8.0.0, sequence_ is just sequenceA_, -- specialized to Monad. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | The sum of a collection of actions, generalizing concat. As of -- base 4.8.0.0, msum is just asum, specialized to -- MonadPlus. msum :: (Foldable t, MonadPlus m) => t (m a) -> m 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 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 with respect to the given -- comparison function. minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | notElem is the negation of elem. notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `notElem` -- | 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 Data.Foldable.Foldable GHC.Generics.V1 instance Data.Foldable.Foldable GHC.Generics.Par1 instance Data.Foldable.Foldable f => Data.Foldable.Foldable (GHC.Generics.Rec1 f) instance Data.Foldable.Foldable (GHC.Generics.K1 i c) instance Data.Foldable.Foldable f => Data.Foldable.Foldable (GHC.Generics.M1 i c f) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (f GHC.Generics.:+: g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (f GHC.Generics.:*: g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (f GHC.Generics.:.: g) instance Data.Foldable.Foldable (GHC.Generics.URec (GHC.Ptr.Ptr ())) instance Data.Foldable.Foldable (GHC.Generics.URec GHC.Types.Char) instance Data.Foldable.Foldable (GHC.Generics.URec GHC.Types.Double) instance Data.Foldable.Foldable (GHC.Generics.URec GHC.Types.Float) instance Data.Foldable.Foldable (GHC.Generics.URec GHC.Types.Int) instance Data.Foldable.Foldable (GHC.Generics.URec GHC.Types.Word) instance Data.Foldable.Foldable GHC.Base.Maybe instance Data.Foldable.Foldable [] instance Data.Foldable.Foldable (Data.Either.Either a) instance Data.Foldable.Foldable ((,) a) instance Data.Foldable.Foldable (GHC.Arr.Array i) instance Data.Foldable.Foldable Data.Proxy.Proxy instance Data.Foldable.Foldable Data.Monoid.Dual instance Data.Foldable.Foldable Data.Monoid.Sum instance Data.Foldable.Foldable Data.Monoid.Product instance Data.Foldable.Foldable Data.Monoid.First instance Data.Foldable.Foldable Data.Monoid.Last instance Data.Foldable.Foldable GHC.Generics.U1 module Data.Functor.Const -- | The Const functor. newtype Const a b Const :: a -> Const a b [getConst] :: Const a b -> a instance forall a k (b :: k). Foreign.Storable.Storable a => Foreign.Storable.Storable (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Real.Real a => GHC.Real.Real (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Classes.Ord a => GHC.Classes.Ord (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Num.Num a => GHC.Num.Num (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Base.Monoid a => GHC.Base.Monoid (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Arr.Ix a => GHC.Arr.Ix (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Real.Integral a => GHC.Real.Integral (Data.Functor.Const.Const a b) instance GHC.Generics.Generic1 (Data.Functor.Const.Const a) instance forall a k (b :: k). GHC.Generics.Generic (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Const.Const a b) instance forall a k (b :: k). Data.Bits.FiniteBits a => Data.Bits.FiniteBits (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Classes.Eq a => GHC.Classes.Eq (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Enum.Enum a => GHC.Enum.Enum (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Functor.Const.Const a b) instance forall a k (b :: k). Data.Bits.Bits a => Data.Bits.Bits (Data.Functor.Const.Const a b) instance forall k a (b :: k). GHC.Read.Read a => GHC.Read.Read (Data.Functor.Const.Const a b) instance forall k a (b :: k). GHC.Show.Show a => GHC.Show.Show (Data.Functor.Const.Const a b) instance Data.Foldable.Foldable (Data.Functor.Const.Const m) instance GHC.Base.Functor (Data.Functor.Const.Const m) instance GHC.Base.Monoid m => GHC.Base.Applicative (Data.Functor.Const.Const m) -- | This provides a type-indexed type representation mechanism, similar to -- that described by, -- -- -- -- The interface provides TypeRep, a type representation which -- can be safely decomposed and composed. See Data.Dynamic for an -- example of this. module Type.Reflection -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable (a :: k) typeRep :: Typeable a => TypeRep a -- | Use a TypeRep as Typeable evidence. withTypeable :: forall a r. TypeRep a -> (Typeable a => r) -> r -- | Propositional equality. If a :~: b is inhabited by some -- terminating value, then the type a is the same as the type -- b. To use this equality in practice, pattern-match on the -- a :~: b to get out the Refl constructor; in the body -- of the pattern-match, the compiler knows that a ~ b. data a (:~:) b [Refl] :: a :~: a -- | Kind heterogeneous propositional equality. Like '(:~:)', a :~~: -- b is inhabited by a terminating value if and only if a -- is the same type as b. data (a :: k1) (:~~:) (b :: k2) [HRefl] :: a :~~: a -- | A concrete representation of a (monomorphic) type. TypeRep -- supports reasonably efficient equality. data TypeRep (a :: k) typeOf :: Typeable a => a -> TypeRep a -- | Pattern match on a type application -- | Pattern match on a type constructor -- | Pattern match on a type constructor including its instantiated kind -- variables. -- | Observe the type constructor of a type representation typeRepTyCon :: TypeRep a -> TyCon -- | Helper to fully evaluate TypeRep for use as -- NFData(rnf) implementation rnfTypeRep :: TypeRep a -> () -- | Type equality eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Maybe (a :~~: b) -- | Observe the kind of a type. typeRepKind :: TypeRep (a :: k) -> TypeRep k splitApps :: TypeRep a -> (TyCon, [SomeTypeRep]) -- | A non-indexed type representation. data SomeTypeRep [SomeTypeRep] :: forall k (a :: k). !(TypeRep a) -> SomeTypeRep -- | Takes a value of type a and returns a concrete representation -- of that type. someTypeRep :: forall proxy a. Typeable a => proxy a -> SomeTypeRep -- | Observe the type constructor of a quantified type representation. someTypeRepTyCon :: SomeTypeRep -> TyCon -- | Helper to fully evaluate SomeTypeRep for use as -- NFData(rnf) implementation rnfSomeTypeRep :: SomeTypeRep -> () data TyCon :: * tyConPackage :: TyCon -> String tyConModule :: TyCon -> String tyConName :: TyCon -> String rnfTyCon :: TyCon -> () data Module :: * moduleName :: Module -> String modulePackage :: Module -> String -- | Helper to fully evaluate TyCon for use as NFData(rnf) -- implementation rnfModule :: Module -> () -- | 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. -- --

Compatibility Notes

-- -- Since GHC 8.2, GHC has supported type-indexed type representations. -- Data.Typeable provides type representations which are qualified -- over this index, providing an interface very similar to the -- Typeable notion seen in previous releases. For the type-indexed -- interface, see Type.Reflection. -- -- Since GHC 7.8, Typeable is poly-kinded. The changes required -- for this might break some old programs involving Typeable. More -- details on this, including how to fix your code, can be found on the -- PolyTypeable wiki page module Data.Typeable -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable (a :: k) -- | Observe a type representation for the type of a value. typeOf :: forall a. Typeable a => a -> TypeRep -- | Takes a value of type a and returns a concrete representation -- of that type. typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep -- | Propositional equality. If a :~: b is inhabited by some -- terminating value, then the type a is the same as the type -- b. To use this equality in practice, pattern-match on the -- a :~: b to get out the Refl constructor; in the body -- of the pattern-match, the compiler knows that a ~ b. data a (:~:) b [Refl] :: a :~: a -- | Kind heterogeneous propositional equality. Like '(:~:)', a :~~: -- b is inhabited by a terminating value if and only if a -- is the same type as b. data (a :: k1) (:~~:) (b :: k2) [HRefl] :: a :~~: a -- | The type-safe cast operation cast :: forall a b. (Typeable a, Typeable b) => a -> Maybe b -- | Extract a witness of equality of two types eqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~: b) -- | A flexible variation parameterised in a type constructor gcast :: forall a b c. (Typeable a, Typeable b) => c a -> Maybe (c b) -- | Cast over k1 -> k2 gcast1 :: forall c t t' a. (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a)) -- | Cast over k1 -> k2 -> k3 gcast2 :: forall c t t' a b. (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b)) -- | A concrete, poly-kinded proxy type data Proxy t Proxy :: Proxy t -- | A quantified type representation. type TypeRep = SomeTypeRep -- | Force a TypeRep to normal form. rnfTypeRep :: TypeRep -> () -- | Show a type representation showsTypeRep :: TypeRep -> ShowS -- | Build a function type. mkFunTy :: TypeRep -> TypeRep -> 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 -- | Splits a type constructor application. Note that if the type -- constructor is polymorphic, this will not return the kinds that were -- used. splitTyConApp :: TypeRep -> (TyCon, [TypeRep]) -- | Observe the argument types of a type representation typeRepArgs :: TypeRep -> [TypeRep] -- | Observe the type constructor of a quantified type representation. typeRepTyCon :: TypeRep -> TyCon -- | Takes a value of type a and returns a concrete representation -- of that type. typeRepFingerprint :: TypeRep -> Fingerprint data TyCon :: * tyConPackage :: TyCon -> String tyConModule :: TyCon -> String tyConName :: TyCon -> String rnfTyCon :: TyCon -> () tyConFingerprint :: TyCon -> Fingerprint typeOf1 :: forall t (a :: *). Typeable t => t a -> TypeRep typeOf2 :: forall t (a :: *) (b :: *). Typeable t => t a b -> TypeRep typeOf3 :: forall t (a :: *) (b :: *) (c :: *). Typeable t => t a b c -> TypeRep typeOf4 :: forall t (a :: *) (b :: *) (c :: *) (d :: *). Typeable t => t a b c d -> TypeRep typeOf5 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *). Typeable t => t a b c d e -> TypeRep typeOf6 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *). Typeable t => t a b c d e f -> TypeRep typeOf7 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *) (g :: *). Typeable t => t a b c d e f g -> TypeRep -- | Deprecated: renamed to Typeable type Typeable1 (a :: * -> *) = Typeable a -- | Deprecated: renamed to Typeable type Typeable2 (a :: * -> * -> *) = Typeable a -- | Deprecated: renamed to Typeable type Typeable3 (a :: * -> * -> * -> *) = Typeable a -- | Deprecated: renamed to Typeable type Typeable4 (a :: * -> * -> * -> * -> *) = Typeable a -- | Deprecated: renamed to Typeable type Typeable5 (a :: * -> * -> * -> * -> * -> *) = Typeable a -- | Deprecated: renamed to Typeable type Typeable6 (a :: * -> * -> * -> * -> * -> * -> *) = Typeable a -- | Deprecated: renamed to Typeable type Typeable7 (a :: * -> * -> * -> * -> * -> * -> * -> *) = Typeable 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 -- | 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. -- | Deprecated: Safe is now the default, please use Foreign.ForeignPtr -- instead 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. -- -- Note that the foreign function must use the ccall -- calling convention. 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. module Foreign.ForeignPtr -- | 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. -- -- Note that the foreign function must use the ccall -- calling convention. 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 -- | Advances the given address by the given offset in bytes. -- -- The new ForeignPtr shares the finalizer of the original, -- equivalent from a finalization standpoint to just creating another -- reference to the original. That is, the finalizer will not be called -- before the new ForeignPtr is unreachable, nor will it be called -- an additional time due to this call, and the finalizer will be called -- with the same address that it would have had this call not happened, -- *not* the new address. plusForeignPtr :: ForeignPtr a -> Int -> 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) -- | 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 example, 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 GHC.Classes.Eq GHC.IO.Buffer.BufferState -- | Types for text encoding/decoding module GHC.IO.Encoding.Types data BufferCodec from to state BufferCodec :: CodeBuffer from 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. -- -- If multiple CodingProgress returns are possible, OutputUnderflow must -- be preferred to InvalidSequence. This allows GHC's IO library to -- assume that if we observe InvalidSequence there is at least a single -- element available in the output buffer. -- -- 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. [encode] :: BufferCodec from to state -> CodeBuffer from 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 CodeBuffer from to = Buffer from -> Buffer to -> IO (CodingProgress, Buffer from, Buffer to) type EncodeBuffer = CodeBuffer Char Word8 type DecodeBuffer = CodeBuffer Word8 Char data CodingProgress -- | Stopped because the input contains insufficient available elements, or -- all of the input sequence has been successfully 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 GHC.Show.Show GHC.IO.Encoding.Types.CodingProgress instance GHC.Classes.Eq GHC.IO.Encoding.Types.CodingProgress instance GHC.Show.Show GHC.IO.Encoding.Types.TextEncoding -- | 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. -- -- Be warned that modifyIORef does not apply the function -- strictly. This means if the program calls modifyIORef many -- times, but seldomly uses the value, thunks will pile up in memory -- resulting in a space leak. This is a common mistake made when using an -- IORef as a counter. For example, the following will likely produce a -- stack overflow: -- --
--   ref <- newIORef 0
--   replicateM_ 1000000 $ modifyIORef ref (+1)
--   readIORef ref >>= print
--   
-- -- To avoid this problem, use modifyIORef' instead. modifyIORef :: IORef a -> (a -> a) -> IO () -- | Strict version of modifyIORef 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 does not apply the function strictly. This is -- important to know even if all you are doing is replacing the value. -- For example, this will leak memory: -- --
--   ref <- newIORef '1'
--   forever $ atomicModifyIORef ref (\_ -> ('2', ()))
--   
-- -- Use atomicModifyIORef' or atomicWriteIORef to avoid this -- problem. atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b -- | Strict version of atomicModifyIORef. This forces both the value -- stored in the IORef as well as the value returned. atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b -- | Variant of writeIORef with the "barrier to reordering" property -- that atomicModifyIORef has. atomicWriteIORef :: IORef a -> a -> IO () -- | 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)) -- | 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 up to the specified number of bytes, returning the number of -- bytes actually read. This function should only block if there is no -- data available. If there is not enough data available, then the -- function should just return the available data. A return value of zero -- indicates that the end of the data stream (e.g. end of file) has been -- reached. read :: RawIO a => a -> Ptr Word8 -> Int -> IO Int -- | Read up to the specified number of bytes, returning the number of -- bytes actually read, or Nothing if the end of the stream has -- been reached. readNonBlocking :: RawIO a => a -> Ptr Word8 -> Int -> IO (Maybe Int) -- | Write the specified number of bytes. write :: RawIO a => a -> Ptr Word8 -> Int -> IO () -- | Write up to the specified number of bytes without blocking. Returns -- the actual number of bytes written. writeNonBlocking :: RawIO a => a -> Ptr Word8 -> Int -> IO Int -- | I/O operations required for implementing a Handle. class IODevice a -- | ready dev write msecs returns True if the device has -- data to read (if write is False) or space to write new -- data (if write is True). msecs specifies how -- long to wait, in milliseconds. ready :: IODevice a => a -> Bool -> Int -> IO Bool -- | closes the device. Further operations on the device should produce -- exceptions. close :: IODevice a => a -> IO () -- | returns True if the device is a terminal or console. isTerminal :: IODevice a => a -> IO Bool -- | returns True if the device supports seek operations. isSeekable :: IODevice a => a -> IO Bool -- | seek to the specified position in the data. seek :: IODevice a => a -> SeekMode -> Integer -> IO () -- | return the current position in the data. tell :: IODevice a => a -> IO Integer -- | return the size of the data. getSize :: IODevice a => a -> IO Integer -- | change the size of the data. setSize :: IODevice a => a -> Integer -> IO () -- | for terminal devices, changes whether characters are echoed on the -- device. setEcho :: IODevice a => a -> Bool -> IO () -- | returns the current echoing status. getEcho :: IODevice a => a -> IO Bool -- | some devices (e.g. terminals) support a "raw" mode where characters -- entered are immediately made available to the program. If available, -- this operations enables raw mode. setRaw :: IODevice a => a -> Bool -> IO () -- | returns the IODeviceType corresponding to this device. devType :: IODevice a => a -> IO IODeviceType -- | duplicates the device, if possible. The new device is expected to -- share a file pointer with the original device (like Unix -- dup). dup :: IODevice a => a -> IO a -- | dup2 source target replaces the target device with the source -- device. The target device is closed first, if necessary, and then it -- is made into a duplicate of the first device (like Unix -- dup2). 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 GHC.Show.Show GHC.IO.Device.SeekMode instance GHC.Read.Read GHC.IO.Device.SeekMode instance GHC.Enum.Enum GHC.IO.Device.SeekMode instance GHC.Arr.Ix GHC.IO.Device.SeekMode instance GHC.Classes.Ord GHC.IO.Device.SeekMode instance GHC.Classes.Eq GHC.IO.Device.SeekMode instance GHC.Classes.Eq GHC.IO.Device.IODeviceType -- | 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 -- | allocate a new buffer. The size of the buffer is at the discretion of -- the device; e.g. for a memory-mapped file the buffer will probably -- cover the entire file. newBuffer :: BufferedIO dev => dev -> BufferState -> IO (Buffer Word8) -- | reads bytes into the buffer, blocking if there are no bytes available. -- Returns the number of bytes read (zero indicates end-of-file), and the -- new buffer. fillReadBuffer :: BufferedIO dev => dev -> Buffer Word8 -> IO (Int, Buffer Word8) -- | reads bytes into the buffer without blocking. Returns the number of -- bytes read (Nothing indicates end-of-file), and the new buffer. fillReadBuffer0 :: BufferedIO dev => dev -> Buffer Word8 -> IO (Maybe Int, Buffer Word8) -- | Prepares an empty write buffer. This lets the device decide how to set -- up a write buffer: the buffer may need to point to a specific location -- in memory, for example. This is typically used by the client when -- switching from reading to writing on a buffered read/write device. -- -- There is no corresponding operation for read buffers, because before -- reading the client will always call fillReadBuffer. emptyWriteBuffer :: BufferedIO dev => dev -> Buffer Word8 -> IO (Buffer Word8) -- | Flush all the data from the supplied write buffer out to the device. -- The returned buffer should be empty, and ready for writing. flushWriteBuffer :: BufferedIO dev => dev -> Buffer Word8 -> IO (Buffer Word8) -- | Flush data from the supplied write buffer out to the device without -- blocking. Returns the number of bytes written and the remaining -- buffer. 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) -- | 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 GHC.Show.Show GHC.IO.Encoding.Failure.CodingFailureMode -- | 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-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 -- | 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 -- | Single-byte encodings that map directly to Unicode code points. -- -- 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 ascii :: TextEncoding mkAscii :: CodingFailureMode -> TextEncoding latin1_decode :: DecodeBuffer ascii_decode :: DecodeBuffer latin1_encode :: EncodeBuffer latin1_checked_encode :: EncodeBuffer ascii_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 -- | Deprecated: use void instead void :: IO a -> IO () -- | 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) -- | Like malloc but memory is filled with bytes of value zero. calloc :: Storable a => IO (Ptr a) -- | Llike mallocBytes but memory is filled with bytes of value -- zero. callocBytes :: 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 -- | 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 () -- | Fill a given number of bytes in memory area with a byte value. fillBytes :: Ptr a -> Word8 -> 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) -- | Like mallocArray, but allocated memory is filled with bytes of -- value zero. callocArray :: Storable a => Int -> IO (Ptr a) -- | Like callocArray0, but allocated memory is filled with bytes of -- value zero. callocArray0 :: Storable 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. -- -- newCString :: TextEncoding -> String -> IO CString -- | Marshal a Haskell string into a C string (ie, character array) with -- explicit length information. -- -- newCStringLen :: TextEncoding -> String -> IO CStringLen -- | Marshal a Haskell string into a NUL terminated C string using -- temporary storage. -- -- withCString :: TextEncoding -> String -> (CString -> IO a) -> IO a -- | Marshal a Haskell string into a C string (ie, character array) in -- temporary storage, with explicit length information. -- -- withCStringLen :: TextEncoding -> String -> (CStringLen -> IO a) -> IO a -- | Marshal a list of Haskell strings into an array of NUL terminated C -- strings using temporary storage. -- -- withCStringsLen :: TextEncoding -> [String] -> (Int -> Ptr CString -> IO a) -> IO a -- | Determines whether a character can be accurately encoded in a -- CString. -- -- Pretty much anyone who uses this function is in a state of sin because -- whether or not a character is encodable will, in general, depend on -- the context in which it occurs. charIsRepresentable :: TextEncoding -> Char -> IO Bool -- | Utilities for primitive marshalling of C strings. -- -- The marshalling converts each Haskell character, representing a -- Unicode code point, to one or more bytes in a manner that, by default, -- is determined by the current locale. As a consequence, no guarantees -- can be made about the relative length of a Haskell string and its -- corresponding C string, and therefore all the marshalling routines -- include memory allocation. The translation between Unicode and the -- encoding of the current locale may be lossy. module Foreign.C.String -- | A C string is a reference to an array of C characters terminated by -- NUL. type CString = Ptr CChar -- | A string with explicit length information in bytes instead of a -- terminating NUL (allowing NUL characters in the middle of the string). type CStringLen = (Ptr CChar, Int) -- | Marshal a NUL terminated C string into a Haskell string. peekCString :: CString -> IO String -- | Marshal a C string with explicit length into a Haskell string. peekCStringLen :: CStringLen -> IO String -- | Marshal a Haskell string into a NUL terminated C string. -- -- newCString :: String -> IO CString -- | Marshal a Haskell string into a C string (ie, character array) with -- explicit length information. -- -- newCStringLen :: String -> IO CStringLen -- | Marshal a Haskell string into a NUL terminated C string using -- temporary storage. -- -- withCString :: String -> (CString -> IO a) -> IO a -- | Marshal a Haskell string into a C string (ie, character array) in -- temporary storage, with explicit length information. -- -- withCStringLen :: String -> (CStringLen -> IO a) -> IO a charIsRepresentable :: Char -> IO Bool -- | Convert a Haskell character to a C character. This function is only -- safe on the first 256 characters. castCharToCChar :: Char -> CChar -- | Convert a C byte, representing a Latin-1 character, to the -- corresponding Haskell character. castCCharToChar :: CChar -> Char -- | Convert a Haskell character to a C unsigned char. This -- function is only safe on the first 256 characters. castCharToCUChar :: Char -> CUChar -- | Convert a C unsigned char, representing a Latin-1 character, -- to the corresponding Haskell character. castCUCharToChar :: CUChar -> Char -- | Convert a Haskell character to a C signed char. This function -- is only safe on the first 256 characters. castCharToCSChar :: Char -> CSChar -- | Convert a C signed char, representing a Latin-1 character, to -- the corresponding Haskell character. castCSCharToChar :: CSChar -> Char -- | Marshal a NUL terminated C string into a Haskell string. peekCAString :: CString -> IO String -- | Marshal a C string with explicit length into a Haskell string. peekCAStringLen :: CStringLen -> IO String -- | Marshal a Haskell string into a NUL terminated C string. -- -- newCAString :: String -> IO CString -- | Marshal a Haskell string into a C string (ie, character array) with -- explicit length information. -- -- newCAStringLen :: String -> IO CStringLen -- | Marshal a Haskell string into a NUL terminated C string using -- temporary storage. -- -- withCAString :: String -> (CString -> IO a) -> IO a -- | Marshal a Haskell string into a C string (ie, character array) in -- temporary storage, with explicit length information. -- -- withCAStringLen :: String -> (CStringLen -> IO a) -> IO a -- | A C wide string is a reference to an array of C wide characters -- terminated by NUL. type CWString = Ptr CWchar -- | A wide character string with explicit length information in -- CWchars instead of a terminating NUL (allowing NUL characters -- in the middle of the string). type CWStringLen = (Ptr CWchar, Int) -- | Marshal a NUL terminated C wide string into a Haskell string. peekCWString :: CWString -> IO String -- | Marshal a C wide string with explicit length into a Haskell string. peekCWStringLen :: CWStringLen -> IO String -- | Marshal a Haskell string into a NUL terminated C wide string. -- -- newCWString :: String -> IO CWString -- | Marshal a Haskell string into a C wide string (ie, wide character -- array) with explicit length information. -- -- newCWStringLen :: String -> IO CWStringLen -- | Marshal a Haskell string into a NUL terminated C wide string using -- temporary storage. -- -- withCWString :: String -> (CWString -> IO a) -> IO a -- | Marshal a Haskell string into a C wide string (i.e. wide character -- array) in temporary storage, with explicit length information. -- -- withCWStringLen :: String -> (CWStringLen -> IO a) -> IO a -- | 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 -- | FFI datatypes and operations that use or require concurrency (GHC -- only). module Foreign.Concurrent -- | Turns a plain memory reference into a foreign object by associating a -- finalizer - given by the monadic operation - with the reference. The -- storage manager will start the finalizer, in a separate thread, some -- time after the last reference to the ForeignPtr is dropped. -- There is no guarantee of promptness, and in fact there is no guarantee -- that the finalizer will eventually run at all. -- -- Note that references from a finalizer do not necessarily prevent -- another object from being finalized. If A's finalizer refers to B -- (perhaps using touchForeignPtr, then the only guarantee is -- that B's finalizer will never be started before A's. If both A and B -- are unreachable, then both finalizers will start together. See -- touchForeignPtr for more on finalizer ordering. newForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a) -- | This function adds a finalizer to the given ForeignPtr. The -- finalizer will run before all other finalizers for the same -- object which have already been registered. -- -- This is a variant of -- Foreign.ForeignPtr.addForeignPtrFinalizer, where the -- finalizer is an arbitrary IO action. When it is invoked, the -- finalizer will run in a new thread. -- -- NB. Be very careful with these finalizers. One common trap is that if -- a finalizer references another finalized value, it does not prevent -- that value from being finalized. In particular, Handles are -- finalized objects, so a finalizer should not refer to a -- Handle (including stdout, stdin or -- stderr). addForeignPtrFinalizer :: ForeignPtr a -> IO () -> IO () -- | C-specific Marshalling support: Handling of C "errno" error codes. module Foreign.C.Error -- | Haskell representation for errno values. The implementation -- is deliberately exposed, to allow users to add their own definitions -- of Errno values. newtype Errno Errno :: CInt -> Errno eOK :: Errno e2BIG :: Errno eACCES :: Errno eADDRINUSE :: Errno eADDRNOTAVAIL :: Errno eADV :: Errno eAFNOSUPPORT :: Errno eAGAIN :: Errno eALREADY :: Errno eBADF :: Errno eBADMSG :: Errno eBADRPC :: Errno eBUSY :: Errno eCHILD :: Errno eCOMM :: Errno eCONNABORTED :: Errno eCONNREFUSED :: Errno eCONNRESET :: Errno eDEADLK :: Errno eDESTADDRREQ :: Errno eDIRTY :: Errno eDOM :: Errno eDQUOT :: Errno eEXIST :: Errno eFAULT :: Errno eFBIG :: Errno eFTYPE :: Errno eHOSTDOWN :: Errno eHOSTUNREACH :: Errno eIDRM :: Errno eILSEQ :: Errno eINPROGRESS :: Errno eINTR :: Errno eINVAL :: Errno eIO :: Errno eISCONN :: Errno eISDIR :: Errno eLOOP :: Errno eMFILE :: Errno eMLINK :: Errno eMSGSIZE :: Errno eMULTIHOP :: Errno eNAMETOOLONG :: Errno eNETDOWN :: Errno eNETRESET :: Errno eNETUNREACH :: Errno eNFILE :: Errno eNOBUFS :: Errno eNODATA :: Errno eNODEV :: Errno eNOENT :: Errno eNOEXEC :: Errno eNOLCK :: Errno eNOLINK :: Errno eNOMEM :: Errno eNOMSG :: Errno eNONET :: Errno eNOPROTOOPT :: Errno eNOSPC :: Errno eNOSR :: Errno eNOSTR :: Errno eNOSYS :: Errno eNOTBLK :: Errno eNOTCONN :: Errno eNOTDIR :: Errno eNOTEMPTY :: Errno eNOTSOCK :: Errno eNOTSUP :: Errno eNOTTY :: Errno eNXIO :: Errno eOPNOTSUPP :: Errno ePERM :: Errno ePFNOSUPPORT :: Errno ePIPE :: Errno ePROCLIM :: Errno ePROCUNAVAIL :: Errno ePROGMISMATCH :: Errno ePROGUNAVAIL :: Errno ePROTO :: Errno ePROTONOSUPPORT :: Errno ePROTOTYPE :: Errno eRANGE :: Errno eREMCHG :: Errno eREMOTE :: Errno eROFS :: Errno eRPCMISMATCH :: Errno eRREMOTE :: Errno eSHUTDOWN :: Errno eSOCKTNOSUPPORT :: Errno eSPIPE :: Errno eSRCH :: Errno eSRMNT :: Errno eSTALE :: Errno eTIME :: Errno eTIMEDOUT :: Errno eTOOMANYREFS :: Errno eTXTBSY :: Errno eUSERS :: Errno eWOULDBLOCK :: Errno eXDEV :: Errno -- | Yield True if the given Errno value is valid on the -- system. This implies that the Eq instance of Errno is -- also system dependent as it is only defined for valid values of -- Errno. isValidErrno :: Errno -> Bool -- | Get the current value of errno in the current thread. getErrno :: IO Errno -- | Reset the current thread's errno value to eOK. resetErrno :: IO () -- | Construct an IOError based on the given Errno value. The -- optional information can be used to improve the accuracy of error -- messages. errnoToIOError :: String -> Errno -> Maybe Handle -> Maybe String -> IOError -- | Throw an IOError corresponding to the current value of -- getErrno. throwErrno :: String -> IO a -- | Throw an IOError corresponding to the current value of -- getErrno if the result value of the IO action meets the -- given predicate. throwErrnoIf :: (a -> Bool) -> String -> IO a -> IO a -- | as throwErrnoIf, but discards the result of the IO -- action after error handling. throwErrnoIf_ :: (a -> Bool) -> String -> IO a -> IO () -- | as throwErrnoIf, but retry the IO action when it yields -- the error code eINTR - this amounts to the standard retry loop -- for interrupted POSIX system calls. throwErrnoIfRetry :: (a -> Bool) -> String -> IO a -> IO a -- | as throwErrnoIfRetry, but discards the result. throwErrnoIfRetry_ :: (a -> Bool) -> String -> IO a -> IO () -- | Throw an IOError corresponding to the current value of -- getErrno if the IO action returns a result of -- -1. throwErrnoIfMinus1 :: (Eq a, Num a) => String -> IO a -> IO a -- | as throwErrnoIfMinus1, but discards the result. throwErrnoIfMinus1_ :: (Eq a, Num a) => String -> IO a -> IO () -- | Throw an IOError corresponding to the current value of -- getErrno if the IO action returns a result of -- -1, but retries in case of an interrupted operation. throwErrnoIfMinus1Retry :: (Eq a, Num a) => String -> IO a -> IO a -- | as throwErrnoIfMinus1, but discards the result. throwErrnoIfMinus1Retry_ :: (Eq a, Num a) => String -> IO a -> IO () -- | Throw an IOError corresponding to the current value of -- getErrno if the IO action returns nullPtr. throwErrnoIfNull :: String -> IO (Ptr a) -> IO (Ptr a) -- | Throw an IOError corresponding to the current value of -- getErrno if the IO action returns nullPtr, but -- retry in case of an interrupted operation. throwErrnoIfNullRetry :: String -> IO (Ptr a) -> IO (Ptr a) -- | as throwErrnoIfRetry, but additionally if the operation yields -- the error code eAGAIN or eWOULDBLOCK, an alternative -- action is executed before retrying. throwErrnoIfRetryMayBlock :: (a -> Bool) -> String -> IO a -> IO b -> IO a -- | as throwErrnoIfRetryMayBlock, but discards the result. throwErrnoIfRetryMayBlock_ :: (a -> Bool) -> String -> IO a -> IO b -> IO () -- | as throwErrnoIfMinus1Retry, but checks for operations that -- would block. throwErrnoIfMinus1RetryMayBlock :: (Eq a, Num a) => String -> IO a -> IO b -> IO a -- | as throwErrnoIfMinus1RetryMayBlock, but discards the result. throwErrnoIfMinus1RetryMayBlock_ :: (Eq a, Num a) => String -> IO a -> IO b -> IO () -- | as throwErrnoIfNullRetry, but checks for operations that would -- block. throwErrnoIfNullRetryMayBlock :: String -> IO (Ptr a) -> IO b -> IO (Ptr a) -- | as throwErrno, but exceptions include the given path when -- appropriate. throwErrnoPath :: String -> FilePath -> IO a -- | as throwErrnoIf, but exceptions include the given path when -- appropriate. throwErrnoPathIf :: (a -> Bool) -> String -> FilePath -> IO a -> IO a -- | as throwErrnoIf_, but exceptions include the given path when -- appropriate. throwErrnoPathIf_ :: (a -> Bool) -> String -> FilePath -> IO a -> IO () -- | as throwErrnoIfNull, but exceptions include the given path when -- appropriate. throwErrnoPathIfNull :: String -> FilePath -> IO (Ptr a) -> IO (Ptr a) -- | as throwErrnoIfMinus1, but exceptions include the given path -- when appropriate. throwErrnoPathIfMinus1 :: (Eq a, Num a) => String -> FilePath -> IO a -> IO a -- | as throwErrnoIfMinus1_, but exceptions include the given path -- when appropriate. throwErrnoPathIfMinus1_ :: (Eq a, Num a) => String -> FilePath -> IO a -> IO () instance GHC.Classes.Eq Foreign.C.Error.Errno -- | Bundles the C specific FFI library functionality module Foreign.C -- | This module contains support for pooled memory management. Under this -- scheme, (re-)allocations belong to a given pool, and everything in a -- pool is deallocated when the pool itself is deallocated. This is -- useful when alloca with its implicit allocation and -- deallocation is not flexible enough, but explicit uses of -- malloc and free are too awkward. module Foreign.Marshal.Pool -- | A memory pool. data Pool -- | Allocate a fresh memory pool. newPool :: IO Pool -- | Deallocate a memory pool and everything which has been allocated in -- the pool itself. freePool :: Pool -> IO () -- | Execute an action with a fresh memory pool, which gets automatically -- deallocated (including its contents) after the action has finished. withPool :: (Pool -> IO b) -> IO b -- | Allocate space for storable type in the given pool. The size of the -- area allocated is determined by the sizeOf method from the -- instance of Storable for the appropriate type. pooledMalloc :: Storable a => Pool -> IO (Ptr a) -- | Allocate the given number of bytes of storage in the pool. pooledMallocBytes :: Pool -> Int -> IO (Ptr a) -- | Adjust the storage area for an element in the pool to the given size -- of the required type. pooledRealloc :: Storable a => Pool -> Ptr a -> IO (Ptr a) -- | Adjust the storage area for an element in the pool to the given size. pooledReallocBytes :: Pool -> Ptr a -> Int -> IO (Ptr a) -- | Allocate storage for the given number of elements of a storable type -- in the pool. pooledMallocArray :: Storable a => Pool -> Int -> IO (Ptr a) -- | Allocate storage for the given number of elements of a storable type -- in the pool, but leave room for an extra element to signal the end of -- the array. pooledMallocArray0 :: Storable a => Pool -> Int -> IO (Ptr a) -- | Adjust the size of an array in the given pool. pooledReallocArray :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a) -- | Adjust the size of an array with an end marker in the given pool. pooledReallocArray0 :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a) -- | Allocate storage for a value in the given pool and marshal the value -- into this storage. pooledNew :: Storable a => Pool -> a -> IO (Ptr a) -- | Allocate consecutive storage for a list of values in the given pool -- and marshal these values into it. pooledNewArray :: Storable a => Pool -> [a] -> IO (Ptr a) -- | Allocate consecutive storage for a list of values in the given pool -- and marshal these values into it, terminating the end with the given -- marker. pooledNewArray0 :: Storable a => Pool -> a -> [a] -> IO (Ptr a) -- | Marshalling support -- -- Safe API Only. -- | Deprecated: Safe is now the default, please use Foreign.Marshal -- instead module Foreign.Marshal.Safe -- | Marshalling support module Foreign.Marshal -- | A collection of data types, classes, and functions for interfacing -- with another programming language. -- -- Safe API Only. -- | Deprecated: Safe is now the default, please use Foreign instead module Foreign.Safe -- | A collection of data types, classes, and functions for interfacing -- with another programming language. module Foreign -- | 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 {-# CTYPE "mode_t" #-} 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 {-# CTYPE "blksize_t" #-} CBlkSize CBlkSize :: Int64 -> CBlkSize newtype {-# CTYPE "blkcnt_t" #-} CBlkCnt CBlkCnt :: Int64 -> CBlkCnt newtype {-# CTYPE "clockid_t" #-} CClockId CClockId :: Int32 -> CClockId newtype {-# CTYPE "fsblkcnt_t" #-} CFsBlkCnt CFsBlkCnt :: Word64 -> CFsBlkCnt newtype {-# CTYPE "fsfilcnt_t" #-} CFsFilCnt CFsFilCnt :: Word64 -> CFsFilCnt newtype {-# CTYPE "id_t" #-} CId CId :: Word32 -> CId newtype {-# CTYPE "key_t" #-} CKey CKey :: Int32 -> CKey newtype {-# CTYPE "timer_t" #-} CTimer CTimer :: (Ptr ()) -> CTimer 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 GHC.Show.Show System.Posix.Types.Fd instance GHC.Read.Read System.Posix.Types.Fd instance Data.Bits.FiniteBits System.Posix.Types.Fd instance Data.Bits.Bits System.Posix.Types.Fd instance GHC.Real.Integral System.Posix.Types.Fd instance GHC.Enum.Bounded System.Posix.Types.Fd instance GHC.Real.Real System.Posix.Types.Fd instance Foreign.Storable.Storable System.Posix.Types.Fd instance GHC.Enum.Enum System.Posix.Types.Fd instance GHC.Num.Num System.Posix.Types.Fd instance GHC.Classes.Ord System.Posix.Types.Fd instance GHC.Classes.Eq System.Posix.Types.Fd instance GHC.Show.Show System.Posix.Types.CTimer instance Foreign.Storable.Storable System.Posix.Types.CTimer instance GHC.Classes.Ord System.Posix.Types.CTimer instance GHC.Classes.Eq System.Posix.Types.CTimer instance GHC.Show.Show System.Posix.Types.CKey instance GHC.Read.Read System.Posix.Types.CKey instance Data.Bits.FiniteBits System.Posix.Types.CKey instance Data.Bits.Bits System.Posix.Types.CKey instance GHC.Real.Integral System.Posix.Types.CKey instance GHC.Enum.Bounded System.Posix.Types.CKey instance GHC.Real.Real System.Posix.Types.CKey instance Foreign.Storable.Storable System.Posix.Types.CKey instance GHC.Enum.Enum System.Posix.Types.CKey instance GHC.Num.Num System.Posix.Types.CKey instance GHC.Classes.Ord System.Posix.Types.CKey instance GHC.Classes.Eq System.Posix.Types.CKey instance GHC.Show.Show System.Posix.Types.CId instance GHC.Read.Read System.Posix.Types.CId instance Data.Bits.FiniteBits System.Posix.Types.CId instance Data.Bits.Bits System.Posix.Types.CId instance GHC.Real.Integral System.Posix.Types.CId instance GHC.Enum.Bounded System.Posix.Types.CId instance GHC.Real.Real System.Posix.Types.CId instance Foreign.Storable.Storable System.Posix.Types.CId instance GHC.Enum.Enum System.Posix.Types.CId instance GHC.Num.Num System.Posix.Types.CId instance GHC.Classes.Ord System.Posix.Types.CId instance GHC.Classes.Eq System.Posix.Types.CId instance GHC.Show.Show System.Posix.Types.CFsFilCnt instance GHC.Read.Read System.Posix.Types.CFsFilCnt instance Data.Bits.FiniteBits System.Posix.Types.CFsFilCnt instance Data.Bits.Bits System.Posix.Types.CFsFilCnt instance GHC.Real.Integral System.Posix.Types.CFsFilCnt instance GHC.Enum.Bounded System.Posix.Types.CFsFilCnt instance GHC.Real.Real System.Posix.Types.CFsFilCnt instance Foreign.Storable.Storable System.Posix.Types.CFsFilCnt instance GHC.Enum.Enum System.Posix.Types.CFsFilCnt instance GHC.Num.Num System.Posix.Types.CFsFilCnt instance GHC.Classes.Ord System.Posix.Types.CFsFilCnt instance GHC.Classes.Eq System.Posix.Types.CFsFilCnt instance GHC.Show.Show System.Posix.Types.CFsBlkCnt instance GHC.Read.Read System.Posix.Types.CFsBlkCnt instance Data.Bits.FiniteBits System.Posix.Types.CFsBlkCnt instance Data.Bits.Bits System.Posix.Types.CFsBlkCnt instance GHC.Real.Integral System.Posix.Types.CFsBlkCnt instance GHC.Enum.Bounded System.Posix.Types.CFsBlkCnt instance GHC.Real.Real System.Posix.Types.CFsBlkCnt instance Foreign.Storable.Storable System.Posix.Types.CFsBlkCnt instance GHC.Enum.Enum System.Posix.Types.CFsBlkCnt instance GHC.Num.Num System.Posix.Types.CFsBlkCnt instance GHC.Classes.Ord System.Posix.Types.CFsBlkCnt instance GHC.Classes.Eq System.Posix.Types.CFsBlkCnt instance GHC.Show.Show System.Posix.Types.CClockId instance GHC.Read.Read System.Posix.Types.CClockId instance Data.Bits.FiniteBits System.Posix.Types.CClockId instance Data.Bits.Bits System.Posix.Types.CClockId instance GHC.Real.Integral System.Posix.Types.CClockId instance GHC.Enum.Bounded System.Posix.Types.CClockId instance GHC.Real.Real System.Posix.Types.CClockId instance Foreign.Storable.Storable System.Posix.Types.CClockId instance GHC.Enum.Enum System.Posix.Types.CClockId instance GHC.Num.Num System.Posix.Types.CClockId instance GHC.Classes.Ord System.Posix.Types.CClockId instance GHC.Classes.Eq System.Posix.Types.CClockId instance GHC.Show.Show System.Posix.Types.CBlkCnt instance GHC.Read.Read System.Posix.Types.CBlkCnt instance Data.Bits.FiniteBits System.Posix.Types.CBlkCnt instance Data.Bits.Bits System.Posix.Types.CBlkCnt instance GHC.Real.Integral System.Posix.Types.CBlkCnt instance GHC.Enum.Bounded System.Posix.Types.CBlkCnt instance GHC.Real.Real System.Posix.Types.CBlkCnt instance Foreign.Storable.Storable System.Posix.Types.CBlkCnt instance GHC.Enum.Enum System.Posix.Types.CBlkCnt instance GHC.Num.Num System.Posix.Types.CBlkCnt instance GHC.Classes.Ord System.Posix.Types.CBlkCnt instance GHC.Classes.Eq System.Posix.Types.CBlkCnt instance GHC.Show.Show System.Posix.Types.CBlkSize instance GHC.Read.Read System.Posix.Types.CBlkSize instance Data.Bits.FiniteBits System.Posix.Types.CBlkSize instance Data.Bits.Bits System.Posix.Types.CBlkSize instance GHC.Real.Integral System.Posix.Types.CBlkSize instance GHC.Enum.Bounded System.Posix.Types.CBlkSize instance GHC.Real.Real System.Posix.Types.CBlkSize instance Foreign.Storable.Storable System.Posix.Types.CBlkSize instance GHC.Enum.Enum System.Posix.Types.CBlkSize instance GHC.Num.Num System.Posix.Types.CBlkSize instance GHC.Classes.Ord System.Posix.Types.CBlkSize instance GHC.Classes.Eq System.Posix.Types.CBlkSize instance GHC.Show.Show System.Posix.Types.CRLim instance GHC.Read.Read System.Posix.Types.CRLim instance Data.Bits.FiniteBits System.Posix.Types.CRLim instance Data.Bits.Bits System.Posix.Types.CRLim instance GHC.Real.Integral System.Posix.Types.CRLim instance GHC.Enum.Bounded System.Posix.Types.CRLim instance GHC.Real.Real System.Posix.Types.CRLim instance Foreign.Storable.Storable System.Posix.Types.CRLim instance GHC.Enum.Enum System.Posix.Types.CRLim instance GHC.Num.Num System.Posix.Types.CRLim instance GHC.Classes.Ord System.Posix.Types.CRLim instance GHC.Classes.Eq System.Posix.Types.CRLim instance GHC.Show.Show System.Posix.Types.CTcflag instance GHC.Read.Read System.Posix.Types.CTcflag instance Data.Bits.FiniteBits System.Posix.Types.CTcflag instance Data.Bits.Bits System.Posix.Types.CTcflag instance GHC.Real.Integral System.Posix.Types.CTcflag instance GHC.Enum.Bounded System.Posix.Types.CTcflag instance GHC.Real.Real System.Posix.Types.CTcflag instance Foreign.Storable.Storable System.Posix.Types.CTcflag instance GHC.Enum.Enum System.Posix.Types.CTcflag instance GHC.Num.Num System.Posix.Types.CTcflag instance GHC.Classes.Ord System.Posix.Types.CTcflag instance GHC.Classes.Eq System.Posix.Types.CTcflag instance GHC.Show.Show System.Posix.Types.CSpeed instance GHC.Read.Read System.Posix.Types.CSpeed instance GHC.Real.Real System.Posix.Types.CSpeed instance Foreign.Storable.Storable System.Posix.Types.CSpeed instance GHC.Enum.Enum System.Posix.Types.CSpeed instance GHC.Num.Num System.Posix.Types.CSpeed instance GHC.Classes.Ord System.Posix.Types.CSpeed instance GHC.Classes.Eq System.Posix.Types.CSpeed instance GHC.Show.Show System.Posix.Types.CCc instance GHC.Read.Read System.Posix.Types.CCc instance GHC.Real.Real System.Posix.Types.CCc instance Foreign.Storable.Storable System.Posix.Types.CCc instance GHC.Enum.Enum System.Posix.Types.CCc instance GHC.Num.Num System.Posix.Types.CCc instance GHC.Classes.Ord System.Posix.Types.CCc instance GHC.Classes.Eq System.Posix.Types.CCc instance GHC.Show.Show System.Posix.Types.CUid instance GHC.Read.Read System.Posix.Types.CUid instance Data.Bits.FiniteBits System.Posix.Types.CUid instance Data.Bits.Bits System.Posix.Types.CUid instance GHC.Real.Integral System.Posix.Types.CUid instance GHC.Enum.Bounded System.Posix.Types.CUid instance GHC.Real.Real System.Posix.Types.CUid instance Foreign.Storable.Storable System.Posix.Types.CUid instance GHC.Enum.Enum System.Posix.Types.CUid instance GHC.Num.Num System.Posix.Types.CUid instance GHC.Classes.Ord System.Posix.Types.CUid instance GHC.Classes.Eq System.Posix.Types.CUid instance GHC.Show.Show System.Posix.Types.CNlink instance GHC.Read.Read System.Posix.Types.CNlink instance Data.Bits.FiniteBits System.Posix.Types.CNlink instance Data.Bits.Bits System.Posix.Types.CNlink instance GHC.Real.Integral System.Posix.Types.CNlink instance GHC.Enum.Bounded System.Posix.Types.CNlink instance GHC.Real.Real System.Posix.Types.CNlink instance Foreign.Storable.Storable System.Posix.Types.CNlink instance GHC.Enum.Enum System.Posix.Types.CNlink instance GHC.Num.Num System.Posix.Types.CNlink instance GHC.Classes.Ord System.Posix.Types.CNlink instance GHC.Classes.Eq System.Posix.Types.CNlink instance GHC.Show.Show System.Posix.Types.CGid instance GHC.Read.Read System.Posix.Types.CGid instance Data.Bits.FiniteBits System.Posix.Types.CGid instance Data.Bits.Bits System.Posix.Types.CGid instance GHC.Real.Integral System.Posix.Types.CGid instance GHC.Enum.Bounded System.Posix.Types.CGid instance GHC.Real.Real System.Posix.Types.CGid instance Foreign.Storable.Storable System.Posix.Types.CGid instance GHC.Enum.Enum System.Posix.Types.CGid instance GHC.Num.Num System.Posix.Types.CGid instance GHC.Classes.Ord System.Posix.Types.CGid instance GHC.Classes.Eq System.Posix.Types.CGid instance GHC.Show.Show System.Posix.Types.CSsize instance GHC.Read.Read System.Posix.Types.CSsize instance Data.Bits.FiniteBits System.Posix.Types.CSsize instance Data.Bits.Bits System.Posix.Types.CSsize instance GHC.Real.Integral System.Posix.Types.CSsize instance GHC.Enum.Bounded System.Posix.Types.CSsize instance GHC.Real.Real System.Posix.Types.CSsize instance Foreign.Storable.Storable System.Posix.Types.CSsize instance GHC.Enum.Enum System.Posix.Types.CSsize instance GHC.Num.Num System.Posix.Types.CSsize instance GHC.Classes.Ord System.Posix.Types.CSsize instance GHC.Classes.Eq System.Posix.Types.CSsize instance GHC.Show.Show System.Posix.Types.CPid instance GHC.Read.Read System.Posix.Types.CPid instance Data.Bits.FiniteBits System.Posix.Types.CPid instance Data.Bits.Bits System.Posix.Types.CPid instance GHC.Real.Integral System.Posix.Types.CPid instance GHC.Enum.Bounded System.Posix.Types.CPid instance GHC.Real.Real System.Posix.Types.CPid instance Foreign.Storable.Storable System.Posix.Types.CPid instance GHC.Enum.Enum System.Posix.Types.CPid instance GHC.Num.Num System.Posix.Types.CPid instance GHC.Classes.Ord System.Posix.Types.CPid instance GHC.Classes.Eq System.Posix.Types.CPid instance GHC.Show.Show System.Posix.Types.COff instance GHC.Read.Read System.Posix.Types.COff instance Data.Bits.FiniteBits System.Posix.Types.COff instance Data.Bits.Bits System.Posix.Types.COff instance GHC.Real.Integral System.Posix.Types.COff instance GHC.Enum.Bounded System.Posix.Types.COff instance GHC.Real.Real System.Posix.Types.COff instance Foreign.Storable.Storable System.Posix.Types.COff instance GHC.Enum.Enum System.Posix.Types.COff instance GHC.Num.Num System.Posix.Types.COff instance GHC.Classes.Ord System.Posix.Types.COff instance GHC.Classes.Eq System.Posix.Types.COff instance GHC.Show.Show System.Posix.Types.CMode instance GHC.Read.Read System.Posix.Types.CMode instance Data.Bits.FiniteBits System.Posix.Types.CMode instance Data.Bits.Bits System.Posix.Types.CMode instance GHC.Real.Integral System.Posix.Types.CMode instance GHC.Enum.Bounded System.Posix.Types.CMode instance GHC.Real.Real System.Posix.Types.CMode instance Foreign.Storable.Storable System.Posix.Types.CMode instance GHC.Enum.Enum System.Posix.Types.CMode instance GHC.Num.Num System.Posix.Types.CMode instance GHC.Classes.Ord System.Posix.Types.CMode instance GHC.Classes.Eq System.Posix.Types.CMode instance GHC.Show.Show System.Posix.Types.CIno instance GHC.Read.Read System.Posix.Types.CIno instance Data.Bits.FiniteBits System.Posix.Types.CIno instance Data.Bits.Bits System.Posix.Types.CIno instance GHC.Real.Integral System.Posix.Types.CIno instance GHC.Enum.Bounded System.Posix.Types.CIno instance GHC.Real.Real System.Posix.Types.CIno instance Foreign.Storable.Storable System.Posix.Types.CIno instance GHC.Enum.Enum System.Posix.Types.CIno instance GHC.Num.Num System.Posix.Types.CIno instance GHC.Classes.Ord System.Posix.Types.CIno instance GHC.Classes.Eq System.Posix.Types.CIno instance GHC.Show.Show System.Posix.Types.CDev instance GHC.Read.Read System.Posix.Types.CDev instance Data.Bits.FiniteBits System.Posix.Types.CDev instance Data.Bits.Bits System.Posix.Types.CDev instance GHC.Real.Integral System.Posix.Types.CDev instance GHC.Enum.Bounded System.Posix.Types.CDev instance GHC.Real.Real System.Posix.Types.CDev instance Foreign.Storable.Storable System.Posix.Types.CDev instance GHC.Enum.Enum System.Posix.Types.CDev instance GHC.Num.Num System.Posix.Types.CDev instance GHC.Classes.Ord System.Posix.Types.CDev instance GHC.Classes.Eq System.Posix.Types.CDev -- | The Dynamic interface provides basic support for dynamic types. -- -- Operations for injecting values of arbitrary type into a dynamically -- typed value, Dynamic, are provided, together with operations for -- converting dynamic values into a concrete (monomorphic) type. module Data.Dynamic -- | A value of type Dynamic is an object encapsulated together with -- its type. -- -- A Dynamic may only represent a monomorphic value; an attempt to -- create a value of type Dynamic from a polymorphically-typed -- expression will result in an ambiguity error (see toDyn). -- -- Showing a value of type Dynamic returns a pretty-printed -- representation of the object's type; useful for debugging. data Dynamic [Dynamic] :: forall a. TypeRep a -> a -> Dynamic -- | Converts an arbitrary value into an object of type Dynamic. -- -- The type of the object must be an instance of Typeable, which -- ensures that only monomorphically-typed objects may be converted to -- Dynamic. To convert a polymorphic object into Dynamic, -- give it a monomorphic type signature. For example: -- --
--   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 :: forall a. Typeable a => Dynamic -> Maybe a dynApply :: Dynamic -> Dynamic -> Maybe Dynamic dynApp :: Dynamic -> Dynamic -> Dynamic dynTypeRep :: Dynamic -> SomeTypeRep -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable (a :: k) instance GHC.Show.Show Data.Dynamic.Dynamic instance GHC.Exception.Exception Data.Dynamic.Dynamic -- | 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. data ThreadId ThreadId :: ThreadId# -> ThreadId -- | Creates a new thread to run the IO computation passed as the -- first argument, and returns the ThreadId of the newly created -- thread. -- -- The new thread will be a lightweight, unbound thread. Foreign -- calls made by this thread are not guaranteed to be made by any -- particular OS thread; if you need foreign calls to be made by a -- particular OS thread, then use forkOS instead. -- -- The new thread inherits the masked state of the parent (see -- mask). -- -- The newly created thread has an exception handler that discards the -- exceptions BlockedIndefinitelyOnMVar, -- BlockedIndefinitelyOnSTM, and ThreadKilled, and passes -- all other exceptions to the uncaught exception handler. forkIO :: 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 capability the -- thread should run. Unlike a forkIO thread, a thread created by -- forkOn will stay on the same capability for its entire lifetime -- (forkIO threads can migrate between capabilities according to -- the scheduling policy). forkOn is useful for overriding the -- scheduling policy when you know in advance how best to distribute the -- threads. -- -- The Int argument specifies a capability number (see -- getNumCapabilities). Typically capabilities correspond to -- physical processors, but the exact behaviour is -- implementation-dependent. The value passed to forkOn is -- interpreted modulo the total number of capabilities as returned by -- getNumCapabilities. -- -- GHC note: the number of capabilities is specified by the +RTS -- -N option when the program is started. Capabilities can be fixed -- to actual processor cores with +RTS -qa if the underlying -- operating system supports that, although in practice this is usually -- unnecessary (and may actually degrade performance in some cases - -- experimentation is recommended). 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 -- | 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. To -- change this value, use setNumCapabilities. getNumCapabilities :: IO Int -- | Set 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. The initial value -- is given by the +RTS -N runtime flag. -- -- This is also the number of threads that will participate in parallel -- garbage collection. It is strongly recommended that the number of -- capabilities is not set larger than the number of physical processor -- cores, and it may often be beneficial to leave one or more cores free -- to avoid contention with other processes in the machine. setNumCapabilities :: Int -> IO () -- | Returns the number of CPUs that the machine has 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). -- -- Exception delivery synchronizes between the source and target thread: -- 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. Exception delivery is also -- atomic with respect to other exceptions. Atomicity is a useful -- property to have when dealing with race conditions: e.g. 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 infixr 0 `par` pseq :: a -> b -> b infixr 0 `pseq` -- | 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 () -- | make a weak pointer to a ThreadId. It can be important to do -- this if you want to hold a reference to a ThreadId while still -- allowing the thread to receive the BlockedIndefinitely family -- of exceptions (e.g. BlockedIndefinitelyOnMVar). Holding a -- normal ThreadId reference will prevent the delivery of -- BlockedIndefinitely exceptions because the reference could be -- used as the target of throwTo at any time, which would unblock -- the thread. -- -- Holding a Weak ThreadId, on the other hand, will not prevent -- the thread from receiving BlockedIndefinitely exceptions. It -- is still possible to throw an exception to a Weak ThreadId, -- but the caller must use deRefWeak first to determine whether -- the thread still exists. mkWeakThreadId :: ThreadId -> IO (Weak ThreadId) -- | 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 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) -- | Make a StablePtr that can be passed to the C function -- hs_try_putmvar(). The RTS wants a StablePtr to the -- underlying MVar#, but a StablePtr# can only refer to -- lifted types, so we have to cheat by coercing. newStablePtrPrimMVar :: MVar () -> IO (StablePtr PrimMVar) data PrimMVar -- | Every thread has an allocation counter that tracks how much memory has -- been allocated by the thread. The counter is initialized to zero, and -- setAllocationCounter sets the current value. The allocation -- counter counts *down*, so in the absence of a call to -- setAllocationCounter its value is the negation of the number of -- bytes of memory allocated by the thread. -- -- There are two things that you can do with this counter: -- -- -- -- Allocation accounting is accurate only to about 4Kbytes. setAllocationCounter :: Int64 -> IO () -- | Return the current value of the allocation counter for the current -- thread. getAllocationCounter :: IO Int64 -- | Enables the allocation counter to be treated as a limit for the -- current thread. When the allocation limit is enabled, if the -- allocation counter counts down below zero, the thread will be sent the -- AllocationLimitExceeded asynchronous exception. When this -- happens, the counter is reinitialised (by default to 100K, but tunable -- with the +RTS -xq option) so that it can handle the exception -- and perform any necessary clean up. If it exhausts this additional -- allowance, another AllocationLimitExceeded exception is sent, -- and so forth. Like other asynchronous exceptions, the -- AllocationLimitExceeded exception is deferred while the thread -- is inside mask or an exception handler in catch. -- -- Note that memory allocation is unrelated to live memory, also -- known as heap residency. A thread can allocate a large amount -- of memory and retain anything between none and all of it. It is better -- to think of the allocation limit as a limit on CPU time, rather -- than a limit on memory. -- -- Compared to using timeouts, allocation limits don't count time spent -- blocked or in foreign calls. enableAllocationLimit :: IO () -- | Disable allocation limit processing for the current thread. disableAllocationLimit :: 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. -- -- unsafeIOToSTM :: IO a -> STM a withMVar :: MVar a -> (a -> IO b) -> IO b modifyMVar_ :: MVar a -> (a -> IO a) -> IO () setUncaughtExceptionHandler :: (SomeException -> IO ()) -> IO () getUncaughtExceptionHandler :: IO (SomeException -> IO ()) reportError :: SomeException -> IO () reportStackOverflow :: IO () reportHeapOverflow :: IO () sharedCAF :: a -> (Ptr a -> IO (Ptr a)) -> IO a instance GHC.Show.Show GHC.Conc.Sync.ThreadStatus instance GHC.Classes.Ord GHC.Conc.Sync.ThreadStatus instance GHC.Classes.Eq GHC.Conc.Sync.ThreadStatus instance GHC.Show.Show GHC.Conc.Sync.BlockReason instance GHC.Classes.Ord GHC.Conc.Sync.BlockReason instance GHC.Classes.Eq GHC.Conc.Sync.BlockReason instance GHC.Classes.Eq (GHC.Conc.Sync.TVar a) instance GHC.Base.Functor GHC.Conc.Sync.STM instance GHC.Base.Applicative GHC.Conc.Sync.STM instance GHC.Base.Monad GHC.Conc.Sync.STM instance GHC.Base.Alternative GHC.Conc.Sync.STM instance GHC.Base.MonadPlus GHC.Conc.Sync.STM instance GHC.Show.Show GHC.Conc.Sync.ThreadId instance GHC.Classes.Eq GHC.Conc.Sync.ThreadId instance GHC.Classes.Ord GHC.Conc.Sync.ThreadId -- | Extensible exceptions, except for multiple handlers. module Control.Exception.Base -- | The SomeException type is the root of the exception type -- hierarchy. When an exception of type e is thrown, behind the -- scenes it is encapsulated in a SomeException. data SomeException SomeException :: e -> SomeException -- | Any type that you wish to throw or catch as an exception must be an -- instance of the Exception class. The simplest case is a new -- exception type directly below the root: -- --
--   data MyException = ThisException | ThatException
--       deriving Show
--   
--   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
--   
--   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
--   
--   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 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 toException :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Render this exception value in a human-friendly manner. -- -- Default implementation: show. displayException :: Exception e => e -> String -- | 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 RatioZeroDenominator :: 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. newtype AssertionFailed AssertionFailed :: String -> AssertionFailed -- | Superclass for asynchronous exceptions. data SomeAsyncException SomeAsyncException :: e -> SomeAsyncException -- | 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: -- -- HeapOverflow :: AsyncException -- | This exception is raised by another thread calling killThread, -- or by the system if it needs to terminate the thread for some reason. ThreadKilled :: AsyncException -- | This exception is raised by default in the main thread of the program -- when the user requests to terminate the program via the usual -- mechanism(s) (e.g. Control-C in the console). UserInterrupt :: AsyncException asyncExceptionToException :: Exception e => e -> SomeException asyncExceptionFromException :: Exception e => SomeException -> Maybe e -- | Thrown when the runtime system detects that the computation is -- guaranteed not to terminate. Note that there is no guarantee that the -- runtime system will notice whether any given computation is guaranteed -- to terminate or not. data NonTermination NonTermination :: NonTermination -- | Thrown when the program attempts to call atomically, from the -- stm package, inside another call to atomically. data NestedAtomically NestedAtomically :: NestedAtomically -- | The thread is blocked on an MVar, but there are no other -- references to the MVar so it can't ever continue. data BlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar :: BlockedIndefinitelyOnMVar -- | The thread is waiting to retry an STM transaction, but there are no -- other references to any TVars involved, so it can't ever -- continue. data BlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM :: BlockedIndefinitelyOnSTM -- | This thread has exceeded its allocation limit. See -- setAllocationCounter and enableAllocationLimit. data AllocationLimitExceeded AllocationLimitExceeded :: AllocationLimitExceeded -- | Compaction found an object that cannot be compacted. Functions cannot -- be compacted, nor can mutable objects or pinned objects. See -- compact. newtype CompactionFailed CompactionFailed :: String -> CompactionFailed -- | There are no runnable threads, so the program is deadlocked. The -- Deadlock exception is raised in the main thread only. data Deadlock Deadlock :: Deadlock -- | A class method without a definition (neither a default definition, nor -- a definition in the appropriate instance) was called. The -- String gives information about which method it was. newtype NoMethodError NoMethodError :: String -> NoMethodError -- | A pattern match failed. The String gives information about -- the source location of the pattern. newtype PatternMatchFail PatternMatchFail :: String -> PatternMatchFail -- | An uninitialised record field was used. The String gives -- information about the source location where the record was -- constructed. newtype RecConError RecConError :: String -> RecConError -- | A record selector was applied to a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. The String gives information about the source -- location of the record selector. newtype RecSelError RecSelError :: String -> RecSelError -- | A record update was performed on a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. The String gives information about the source -- location of the record update. newtype RecUpdError RecUpdError :: String -> RecUpdError -- | This is thrown when the user calls error. The String -- is the argument given to error. data ErrorCall ErrorCallWithLocation :: String -> String -> ErrorCall -- | An expression that didn't typecheck during compile time was called. -- This is only possible with -fdefer-type-errors. The String -- gives details about the failed type check. newtype TypeError TypeError :: String -> TypeError -- | A variant of throw that can only be used within the IO -- monad. -- -- Although throwIO has a type that is an instance of the type of -- throw, the two functions are subtly different: -- --
--   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). -- -- Exception delivery synchronizes between the source and target thread: -- 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. Exception delivery is also -- atomic with respect to other exceptions. Atomicity is a useful -- property to have when dealing with race conditions: e.g. 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. 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)
--   
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 -- | Evaluate the argument to weak head normal form. -- -- evaluate is typically used to uncover any exceptions that a -- lazy value may contain, and possibly handle them. -- -- evaluate only evaluates to weak head normal form. If -- deeper evaluation is needed, the force function from -- Control.DeepSeq may be handy: -- --
--   evaluate $ force x
--   
-- -- There is a subtle difference between evaluate x and -- return $! x, analogous to the difference -- between throwIO and throw. If the lazy value x -- throws an exception, return $! x will fail to -- return an IO action and will throw an exception instead. -- evaluate x, on the other hand, always produces an -- IO action; that action will throw an exception upon -- execution iff x throws an exception upon -- evaluation. -- -- The practical implication of this difference is that due to the -- imprecise exceptions semantics, -- --
--   (return $! error "foo") >> error "bar"
--   
-- -- may throw either "foo" or "bar", depending on the -- optimizations performed by the compiler. On the other hand, -- --
--   evaluate (error "foo") >> error "bar"
--   
-- -- is guaranteed to throw "foo". -- -- The rule of thumb is to use evaluate to force or handle -- exceptions in lazy values. If, on the other hand, you are forcing a -- lazy value for efficiency reasons only and do not care about -- exceptions, you may use return $! x. 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 MaskingState from -- the parent; that is, to start a thread in the -- MaskedInterruptible state, 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 -- forkIOWithUnmask. 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 -- | 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 typeError :: Addr# -> a nonTermination :: SomeException nestedAtomically :: SomeException instance GHC.Show.Show Control.Exception.Base.NestedAtomically instance GHC.Exception.Exception Control.Exception.Base.NestedAtomically instance GHC.Show.Show Control.Exception.Base.NonTermination instance GHC.Exception.Exception Control.Exception.Base.NonTermination instance GHC.Show.Show Control.Exception.Base.TypeError instance GHC.Exception.Exception Control.Exception.Base.TypeError instance GHC.Show.Show Control.Exception.Base.NoMethodError instance GHC.Exception.Exception Control.Exception.Base.NoMethodError instance GHC.Show.Show Control.Exception.Base.RecUpdError instance GHC.Exception.Exception Control.Exception.Base.RecUpdError instance GHC.Show.Show Control.Exception.Base.RecConError instance GHC.Exception.Exception Control.Exception.Base.RecConError instance GHC.Show.Show Control.Exception.Base.RecSelError instance GHC.Exception.Exception Control.Exception.Base.RecSelError instance GHC.Show.Show Control.Exception.Base.PatternMatchFail instance GHC.Exception.Exception Control.Exception.Base.PatternMatchFail -- | Standard IO Errors. module System.IO.Error -- | The Haskell 2010 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 Exception. -- -- In Haskell 2010, 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 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) -- | Catch any IOError that occurs in the computation and throw a -- modified version. modifyIOError :: (IOError -> IOError) -> IO a -> IO a -- | 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: -- -- module Control.Exception -- | The SomeException type is the root of the exception type -- hierarchy. When an exception of type e is thrown, behind the -- scenes it is encapsulated in a SomeException. data SomeException SomeException :: e -> SomeException -- | Any type that you wish to throw or catch as an exception must be an -- instance of the Exception class. The simplest case is a new -- exception type directly below the root: -- --
--   data MyException = ThisException | ThatException
--       deriving Show
--   
--   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
--   
--   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
--   
--   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 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 toException :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Render this exception value in a human-friendly manner. -- -- Default implementation: show. displayException :: Exception e => e -> String -- | 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 RatioZeroDenominator :: 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. newtype AssertionFailed AssertionFailed :: String -> AssertionFailed -- | Superclass for asynchronous exceptions. data SomeAsyncException SomeAsyncException :: e -> SomeAsyncException -- | 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: -- -- HeapOverflow :: AsyncException -- | This exception is raised by another thread calling killThread, -- or by the system if it needs to terminate the thread for some reason. ThreadKilled :: AsyncException -- | This exception is raised by default in the main thread of the program -- when the user requests to terminate the program via the usual -- mechanism(s) (e.g. Control-C in the console). UserInterrupt :: AsyncException asyncExceptionToException :: Exception e => e -> SomeException asyncExceptionFromException :: Exception e => SomeException -> Maybe e -- | Thrown when the runtime system detects that the computation is -- guaranteed not to terminate. Note that there is no guarantee that the -- runtime system will notice whether any given computation is guaranteed -- to terminate or not. data NonTermination NonTermination :: NonTermination -- | Thrown when the program attempts to call atomically, from the -- stm package, inside another call to atomically. data NestedAtomically NestedAtomically :: NestedAtomically -- | The thread is blocked on an MVar, but there are no other -- references to the MVar so it can't ever continue. data BlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar :: BlockedIndefinitelyOnMVar -- | The thread is waiting to retry an STM transaction, but there are no -- other references to any TVars involved, so it can't ever -- continue. data BlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM :: BlockedIndefinitelyOnSTM -- | This thread has exceeded its allocation limit. See -- setAllocationCounter and enableAllocationLimit. data AllocationLimitExceeded AllocationLimitExceeded :: AllocationLimitExceeded -- | Compaction found an object that cannot be compacted. Functions cannot -- be compacted, nor can mutable objects or pinned objects. See -- compact. newtype CompactionFailed CompactionFailed :: String -> CompactionFailed -- | There are no runnable threads, so the program is deadlocked. The -- Deadlock exception is raised in the main thread only. data Deadlock Deadlock :: Deadlock -- | A class method without a definition (neither a default definition, nor -- a definition in the appropriate instance) was called. The -- String gives information about which method it was. newtype NoMethodError NoMethodError :: String -> NoMethodError -- | A pattern match failed. The String gives information about -- the source location of the pattern. newtype PatternMatchFail PatternMatchFail :: String -> PatternMatchFail -- | An uninitialised record field was used. The String gives -- information about the source location where the record was -- constructed. newtype RecConError RecConError :: String -> RecConError -- | A record selector was applied to a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. The String gives information about the source -- location of the record selector. newtype RecSelError RecSelError :: String -> RecSelError -- | A record update was performed on a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. The String gives information about the source -- location of the record update. newtype RecUpdError RecUpdError :: String -> RecUpdError -- | This is thrown when the user calls error. The String -- is the argument given to error. data ErrorCall ErrorCallWithLocation :: String -> String -> ErrorCall -- | An expression that didn't typecheck during compile time was called. -- This is only possible with -fdefer-type-errors. The String -- gives details about the failed type check. newtype TypeError TypeError :: String -> TypeError -- | 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 -- | A variant of throw that can only be used within the IO -- monad. -- -- Although throwIO has a type that is an instance of the type of -- throw, the two functions are subtly different: -- --
--   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). -- -- Exception delivery synchronizes between the source and target thread: -- 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. Exception delivery is also -- atomic with respect to other exceptions. Atomicity is a useful -- property to have when dealing with race conditions: e.g. 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. 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)
--   
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) -- | Evaluate the argument to weak head normal form. -- -- evaluate is typically used to uncover any exceptions that a -- lazy value may contain, and possibly handle them. -- -- evaluate only evaluates to weak head normal form. If -- deeper evaluation is needed, the force function from -- Control.DeepSeq may be handy: -- --
--   evaluate $ force x
--   
-- -- There is a subtle difference between evaluate x and -- return $! x, analogous to the difference -- between throwIO and throw. If the lazy value x -- throws an exception, return $! x will fail to -- return an IO action and will throw an exception instead. -- evaluate x, on the other hand, always produces an -- IO action; that action will throw an exception upon -- execution iff x throws an exception upon -- evaluation. -- -- The practical implication of this difference is that due to the -- imprecise exceptions semantics, -- --
--   (return $! error "foo") >> error "bar"
--   
-- -- may throw either "foo" or "bar", depending on the -- optimizations performed by the compiler. On the other hand, -- --
--   evaluate (error "foo") >> error "bar"
--   
-- -- is guaranteed to throw "foo". -- -- The rule of thumb is to use evaluate to force or handle -- exceptions in lazy values. If, on the other hand, you are forcing a -- lazy value for efficiency reasons only and do not care about -- exceptions, you may use return $! x. 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 MaskingState from -- the parent; that is, to start a thread in the -- MaskedInterruptible state, 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 -- forkIOWithUnmask. 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 -- | Allow asynchronous exceptions to be raised even inside mask, -- making the operation interruptible (see the discussion of -- "Interruptible operations" in Exception). -- -- When called outside mask, or inside uninterruptibleMask, -- this function has no effect. interruptible :: IO a -> IO a -- | When invoked inside mask, this function allows a masked -- asynchronous exception to be raised, if one exists. It is equivalent -- to performing an interruptible operation (see #interruptible), but -- does not involve any actual blocking. -- -- When called outside mask, or inside uninterruptibleMask, -- this function has no effect. allowInterrupt :: IO () -- | 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 instance GHC.Base.Functor Control.Exception.Handler -- | "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: -- -- -- -- It is less well known that unsafePerformIO is not type safe. -- For example: -- --
--   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. It may even happen that one of the duplicated -- IO actions is only run partially, and then interrupted in the middle -- without an exception being raised. Therefore, functions like -- bracket cannot be used safely within -- unsafeDupablePerformIO. unsafeDupablePerformIO :: IO a -> a -- | unsafeInterleaveIO allows an 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 -> do
--      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 -- | Text codecs for I/O module GHC.IO.Encoding data BufferCodec from to state BufferCodec :: CodeBuffer from 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. -- -- If multiple CodingProgress returns are possible, OutputUnderflow must -- be preferred to InvalidSequence. This allows GHC's IO library to -- assume that if we observe InvalidSequence there is at least a single -- element available in the output buffer. -- -- 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. [encode] :: BufferCodec from to state -> CodeBuffer from 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 successfully 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 -- -- -- -- The set of known encodings is system-dependent, but includes at least: -- -- -- -- There is additional notation (borrowed from GNU iconv) for specifying -- how illegal characters are handled: -- -- -- -- In theory, this mechanism allows arbitrary data to be roundtripped via -- a String with no loss of data. In practice, there are two -- limitations to be aware of: -- --
    --
  1. This only stands a chance of working for an encoding which is an -- ASCII superset, as for security reasons we refuse to escape any bytes -- smaller than 128. Many encodings of interest are ASCII supersets (in -- particular, you can assume that the locale encoding is an ASCII -- superset) but many (such as UTF-16) are not.
  2. --
  3. If the underlying encoding is not itself roundtrippable, this -- mechanism can fail. Roundtrippable encodings are those which have an -- injective mapping into Unicode. Almost all encodings meet this -- criteria, but some do not. Notably, Shift-JIS (CP932) and Big5 contain -- several different encodings of the same Unicode codepoint.
  4. --
-- -- On Windows, you can access supported code pages with the prefix -- CP; for example, "CP1250". mkTextEncoding :: String -> IO TextEncoding -- | Access to GHC's call-stack simulation module GHC.Stack.CCS -- | Returns a [String] representing the current call stack. This -- can be useful for debugging. -- -- The implementation uses the call-stack simulation maintained 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] -- | Get the stack trace attached to an object. whoCreated :: a -> IO [String] data CostCentreStack data CostCentre getCurrentCCS :: dummy -> IO (Ptr CostCentreStack) getCCSOf :: a -> IO (Ptr CostCentreStack) clearCCS :: IO a -> IO a ccsCC :: Ptr CostCentreStack -> IO (Ptr CostCentre) ccsParent :: Ptr CostCentreStack -> IO (Ptr CostCentreStack) ccLabel :: Ptr CostCentre -> IO CString ccModule :: Ptr CostCentre -> IO CString ccSrcSpan :: Ptr CostCentre -> IO CString ccsToStrings :: Ptr CostCentreStack -> IO [String] renderStack :: [String] -> String -- | Access to GHC's call-stack simulation module GHC.Stack -- | Like the function error, but appends a stack trace to the error -- message if one is available. -- | Deprecated: error appends the call stack now errorWithStackTrace :: String -> a -- | Returns a [String] representing the current call stack. This -- can be useful for debugging. -- -- The implementation uses the call-stack simulation maintained 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] -- | Get the stack trace attached to an object. whoCreated :: a -> IO [String] -- | CallStacks are a lightweight method of obtaining a partial -- call-stack at any point in the program. -- -- A function can request its call-site with the HasCallStack -- constraint. For example, we can define -- --
--   errorWithCallStack :: HasCallStack => String -> a
--   
-- -- as a variant of error that will get its call-site. We can -- access the call-stack inside errorWithCallStack with -- callStack. -- --
--   errorWithCallStack :: HasCallStack => String -> a
--   errorWithCallStack msg = error (msg ++ "n" ++ prettyCallStack callStack)
--   
-- -- Thus, if we call errorWithCallStack we will get a formatted -- call-stack alongside our error message. -- --
--   >>> errorWithCallStack "die"
--   *** Exception: die
--   CallStack (from HasCallStack):
--     errorWithCallStack, called at <interactive>:2:1 in interactive:Ghci1
--   
-- -- GHC solves HasCallStack constraints in three steps: -- --
    --
  1. If there is a CallStack in scope -- i.e. the enclosing -- function has a HasCallStack constraint -- GHC will append the -- new call-site to the existing CallStack.
  2. --
  3. If there is no CallStack in scope -- e.g. in the GHCi -- session above -- and the enclosing definition does not have an -- explicit type signature, GHC will infer a HasCallStack -- constraint for the enclosing definition (subject to the monomorphism -- restriction).
  4. --
  5. If there is no CallStack in scope and the enclosing -- definition has an explicit type signature, GHC will solve the -- HasCallStack constraint for the singleton CallStack -- containing just the current call-site.
  6. --
-- -- CallStacks do not interact with the RTS and do not require -- compilation with -prof. On the other hand, as they are built -- up explicitly via the HasCallStack constraints, they will -- generally not contain as much information as the simulated call-stacks -- maintained by the RTS. -- -- A CallStack is a [(String, SrcLoc)]. The -- String is the name of function that was called, the -- SrcLoc is the call-site. The list is ordered with the most -- recently called function at the head. -- -- NOTE: The intrepid user may notice that HasCallStack is just an -- alias for an implicit parameter ?callStack :: CallStack. This -- is an implementation detail and should not be considered part -- of the CallStack API, we may decide to change the -- implementation in the future. data CallStack -- | Request a CallStack. -- -- NOTE: The implicit parameter ?callStack :: CallStack is an -- implementation detail and should not be considered part of the -- CallStack API, we may decide to change the implementation in -- the future. type HasCallStack = (?callStack :: CallStack) -- | Return the current CallStack. -- -- Does *not* include the call-site of callStack. callStack :: HasCallStack => CallStack -- | The empty CallStack. emptyCallStack :: CallStack -- | Freeze a call-stack, preventing any further call-sites from being -- appended. -- --
--   pushCallStack callSite (freezeCallStack callStack) = freezeCallStack callStack
--   
freezeCallStack :: CallStack -> CallStack -- | Convert a list of call-sites to a CallStack. fromCallSiteList :: [([Char], SrcLoc)] -> CallStack -- | Extract a list of call-sites from the CallStack. -- -- The list is ordered by most recent call. getCallStack :: CallStack -> [([Char], SrcLoc)] -- | Pop the most recent call-site off the CallStack. -- -- This function, like pushCallStack, has no effect on a frozen -- CallStack. popCallStack :: CallStack -> CallStack -- | Pretty print a CallStack. prettyCallStack :: CallStack -> String -- | Push a call-site onto the stack. -- -- This function has no effect on a frozen CallStack. pushCallStack :: ([Char], SrcLoc) -> CallStack -> CallStack -- | Perform some computation without adding new entries to the -- CallStack. withFrozenCallStack :: HasCallStack => (HasCallStack => a) -> a -- | A single location in the source code. data SrcLoc SrcLoc :: [Char] -> [Char] -> [Char] -> Int -> Int -> Int -> Int -> SrcLoc [srcLocPackage] :: SrcLoc -> [Char] [srcLocModule] :: SrcLoc -> [Char] [srcLocFile] :: SrcLoc -> [Char] [srcLocStartLine] :: SrcLoc -> Int [srcLocStartCol] :: SrcLoc -> Int [srcLocEndLine] :: SrcLoc -> Int [srcLocEndCol] :: SrcLoc -> Int -- | Pretty print a SrcLoc. prettySrcLoc :: SrcLoc -> String data CostCentreStack data CostCentre getCurrentCCS :: dummy -> IO (Ptr CostCentreStack) getCCSOf :: a -> IO (Ptr CostCentreStack) clearCCS :: IO a -> IO a ccsCC :: Ptr CostCentreStack -> IO (Ptr CostCentre) ccsParent :: Ptr CostCentreStack -> IO (Ptr CostCentreStack) ccLabel :: Ptr CostCentre -> IO CString ccModule :: Ptr CostCentre -> IO CString ccSrcSpan :: Ptr CostCentre -> IO CString ccsToStrings :: Ptr CostCentreStack -> IO [String] renderStack :: [String] -> String module GHC.Environment -- | Computation getFullArgs is the "raw" version of -- getArgs, similar to argv in other languages. It -- returns a list of the program's command line arguments, starting with -- the program name, and including those normally eaten by the RTS (+RTS -- ... -RTS). getFullArgs :: IO [String] -- | 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: -- --
    --
  1. As synchronized mutable variables,
  2. --
  3. As channels, with takeMVar and putMVar as receive -- and send, and
  4. --
  5. As a binary semaphore MVar (), with -- takeMVar and putMVar as wait and signal.
  6. --
-- -- They were introduced in the paper "Concurrent Haskell" by Simon -- Peyton Jones, Andrew Gordon and Sigbjorn Finne, though some details of -- their implementation have since then changed (in particular, a put on -- a full MVar used to error, but now merely blocks.) -- --

Applicability

-- -- MVars offer more flexibility than IORefs, but less -- flexibility than STM. They are appropriate for building -- synchronization primitives and performing simple interthread -- communication; however they are very simple and susceptible to race -- conditions, deadlocks or uncaught exceptions. Do not use them if you -- need perform larger atomic operations such as reading from multiple -- variables: use STM instead. -- -- In particular, the "bigger" functions in this module (readMVar, -- swapMVar, withMVar, modifyMVar_ and -- modifyMVar) are simply the composition of a takeMVar -- followed by a putMVar with exception safety. These only have -- atomicity guarantees if all other threads perform a takeMVar -- before a putMVar as well; otherwise, they may block. -- --

Fairness

-- -- No thread can be blocked indefinitely on an MVar unless another -- thread holds that MVar indefinitely. One usual implementation -- of this fairness guarantee is that threads blocked on an MVar -- are served in a first-in-first-out fashion, but this is not guaranteed -- in the semantics. -- --

Gotchas

-- -- Like many other Haskell data structures, MVars are lazy. This -- means that if you place an expensive unevaluated thunk inside an -- MVar, it will be evaluated by the thread that consumes it, not -- the thread that produced it. Be sure to evaluate values to be -- placed in an MVar to the appropriate normal form, or utilize a -- strict MVar provided by the strict-concurrency package. -- --

Ordering

-- -- MVar operations are always observed to take place in the order -- they are written in the program, regardless of the memory model of the -- underlying machine. This is in contrast to IORef operations -- which may appear out-of-order to another thread in some cases. -- --

Example

-- -- Consider the following concurrent data structure, a skip channel. This -- is a channel for an intermittent source of high bandwidth information -- (for example, mouse movement events.) Writing to the channel never -- blocks, and reading from the channel only returns the most recent -- value, or blocks if there are no new values. Multiple readers are -- supported with a dupSkipChan operation. -- -- A skip channel is a pair of MVars. The first MVar -- contains the current value, and a list of semaphores that need to be -- notified when it changes. The second MVar is a semaphore for -- this particular reader: it is full if there is a value in the channel -- that this reader has not read yet, and empty otherwise. -- --
--   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: -- -- takeMVar :: MVar a -> IO a -- | Put a value into an MVar. If the MVar is currently full, -- putMVar will wait until it becomes empty. -- -- There are two further important properties of putMVar: -- -- putMVar :: MVar a -> a -> IO () -- | Atomically read the contents of an MVar. If the MVar is -- currently empty, readMVar will wait until its full. -- readMVar is guaranteed to receive the next putMVar. -- -- readMVar is multiple-wakeup, so when multiple readers are -- blocked on an MVar, all of them are woken up at the same time. -- -- Compatibility note: Prior to base 4.7, readMVar was a -- combination of takeMVar and putMVar. This mean that in -- the presence of other threads attempting to putMVar, -- readMVar could block. Furthermore, readMVar would not -- receive the next putMVar if there was already a pending thread -- blocked on takeMVar. The old behavior can be recovered by -- implementing 'readMVar as follows: -- --
--   readMVar :: MVar a -> IO a
--   readMVar m =
--     mask_ $ do
--       a <- takeMVar m
--       putMVar m a
--       return a
--   
readMVar :: MVar a -> IO a -- | Take a value from an MVar, put a new value into the MVar -- and return the value taken. This function is atomic only if there are -- no other producers for this MVar. swapMVar :: MVar a -> a -> IO a -- | A non-blocking version of takeMVar. The tryTakeMVar -- function returns immediately, with Nothing if the MVar -- was empty, or Just a if the MVar was full with -- contents a. After tryTakeMVar, the MVar is left -- empty. tryTakeMVar :: MVar a -> IO (Maybe a) -- | A non-blocking version of putMVar. The tryPutMVar -- function attempts to put the value a into the MVar, -- returning True if it was successful, or False otherwise. tryPutMVar :: MVar a -> a -> IO Bool -- | Check whether a given MVar is empty. -- -- Notice that the boolean value returned is just a snapshot of the state -- of the MVar. By the time you get to react on its result, the MVar may -- have been filled (or emptied) - so be extremely careful when using -- this operation. Use tryTakeMVar instead if possible. isEmptyMVar :: MVar a -> IO Bool -- | withMVar is an exception-safe wrapper for operating on the -- contents of an MVar. This operation is exception-safe: it will -- replace the original contents of the MVar if an exception is -- raised (see Control.Exception). However, it is only atomic if -- there are no other producers for this MVar. withMVar :: MVar a -> (a -> IO b) -> IO b -- | Like withMVar, but the IO action in the second -- argument is executed with asynchronous exceptions masked. withMVarMasked :: MVar a -> (a -> IO b) -> IO b -- | An exception-safe wrapper for modifying the contents of an -- MVar. Like withMVar, modifyMVar will replace the -- original contents of the MVar if an exception is raised during -- the operation. This function is only atomic if there are no other -- producers for this MVar. modifyMVar_ :: MVar a -> (a -> IO a) -> IO () -- | A slight variation on modifyMVar_ that allows a value to be -- returned (b) in addition to the modified value of the -- MVar. modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b -- | Like modifyMVar_, but the IO action in the second -- argument is executed with asynchronous exceptions masked. modifyMVarMasked_ :: MVar a -> (a -> IO a) -> IO () -- | Like modifyMVar, but the IO action in the second -- argument is executed with asynchronous exceptions masked. modifyMVarMasked :: MVar a -> (a -> IO (a, b)) -> IO b -- | A non-blocking version of readMVar. The tryReadMVar -- function returns immediately, with Nothing if the MVar -- was empty, or Just a if the MVar was full with -- contents a. tryReadMVar :: MVar a -> IO (Maybe a) -- | Make a Weak pointer to an MVar, using the second -- argument as a finalizer to run when MVar is garbage-collected mkWeakMVar :: MVar a -> IO () -> IO (Weak (MVar a)) -- | Deprecated: use mkWeakMVar instead addMVarFinalizer :: MVar a -> IO () -> IO () 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 () runHandlersPtr :: Ptr Word8 -> Signal -> IO () -- | Basic concurrency stuff. module GHC.Conc.IO ensureIOManagerIsRunning :: IO () ioManagerCapabilitiesChanged :: 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 () -- | 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 () -- | Returns an STM action that can be used to wait for data to read from a -- file descriptor. The second returned value is an IO action that can be -- used to deregister interest in the file descriptor. threadWaitReadSTM :: Fd -> IO (STM (), IO ()) -- | Returns an STM action that can be used to wait until data can be -- written to a file descriptor. The second returned value is an IO -- action that can be used to deregister interest in the file descriptor. threadWaitWriteSTM :: Fd -> IO (STM (), 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 () -- | Handle operations implemented by file descriptors (FDs) module GHC.IO.Handle.FD -- | A handle managing input from the Haskell program's standard input -- channel. stdin :: Handle -- | A handle managing output to the Haskell program's standard output -- channel. stdout :: Handle -- | A handle managing output to the Haskell program's standard error -- channel. stderr :: Handle -- | Computation openFile file mode allocates and returns a -- new, open handle to manage the file file. It manages input if -- mode is ReadMode, output if mode is -- WriteMode or AppendMode, and both input and output if -- mode is ReadWriteMode. -- -- If the file does not exist and it is opened for output, it should be -- created as a new file. If mode is WriteMode and the -- file already exists, then it should be truncated to zero length. Some -- operating systems delete empty files, so there is no guarantee that -- the file will exist following an openFile with mode -- WriteMode unless it is subsequently written to successfully. -- The handle is positioned at the end of the file if mode is -- AppendMode, and otherwise at the beginning (in which case its -- internal position is 0). The initial buffer mode is -- implementation-dependent. -- -- This operation may fail with: -- -- -- -- Note: if you will be working with files containing binary data, you'll -- want to be using openBinaryFile. openFile :: FilePath -> IOMode -> IO Handle -- | 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 -- | Like openFile, but opens the file in ordinary blocking mode. -- This can be useful for opening a FIFO for writing: if we open in -- non-blocking mode then the open will fail if there are no readers, -- whereas a blocking open will block until a reader appear. openFileBlocking :: FilePath -> IOMode -> IO Handle mkHandleFromFD :: FD -> IODeviceType -> FilePath -> IOMode -> Bool -> Maybe TextEncoding -> IO Handle -- | Turn an existing file descriptor into a Handle. This is used by -- various external libraries to make Handles. -- -- Makes a binary Handle. This is for historical reasons; it should -- probably be a text Handle with the default encoding and newline -- translation instead. fdToHandle :: FD -> IO Handle -- | Old API kept to avoid breaking clients fdToHandle' :: CInt -> Maybe IODeviceType -> Bool -> FilePath -> IOMode -> Bool -> IO Handle -- | Turn an existing Handle into a file descriptor. This function throws -- an IOError if the Handle does not reference a file descriptor. handleToFd :: Handle -> IO FD module GHC.IO.Handle.Lock -- | Exception thrown by hLock on non-Windows platforms that don't -- support flock. data FileLockingNotSupported FileLockingNotSupported :: FileLockingNotSupported -- | Indicates a mode in which a file should be locked. data LockMode SharedLock :: LockMode ExclusiveLock :: LockMode -- | If a Handle references a file descriptor, attempt to lock -- contents of the underlying file in appropriate mode. If the file is -- already locked in incompatible mode, this function blocks until the -- lock is established. The lock is automatically released upon closing a -- Handle. -- -- Things to be aware of: -- -- 1) This function may block inside a C call. If it does, in order to be -- able to interrupt it with asynchronous exceptions and/or for other -- threads to continue working, you MUST use threaded version of the -- runtime system. -- -- 2) The implementation uses LockFileEx on Windows and -- flock otherwise, hence all of their caveats also apply here. -- -- 3) On non-Windows plaftorms that don't support flock (e.g. -- Solaris) this function throws FileLockingNotImplemented. We -- deliberately choose to not provide fcntl based locking instead because -- of its broken semantics. hLock :: Handle -> LockMode -> IO () -- | Non-blocking version of hLock. hTryLock :: Handle -> LockMode -> IO Bool instance GHC.Show.Show GHC.IO.Handle.Lock.FileLockingNotSupported instance GHC.Exception.Exception GHC.IO.Handle.Lock.FileLockingNotSupported -- | External API for GHC's Handle implementation module GHC.IO.Handle -- | Haskell defines operations to read and write characters from and to -- files, represented by values of type Handle. Each value of -- this type is a handle: a record used by the Haskell run-time -- system to manage I/O with file system objects. A handle has at -- least the following properties: -- -- -- -- Most handles will also have a current I/O position indicating where -- the next input or output operation will occur. A handle is -- readable if it manages only input or both input and output; -- likewise, it is writable if it manages only output or both -- input and output. A handle is open when first allocated. Once -- it is closed it can no longer be used for either input or output, -- though an implementation cannot re-use its storage while references -- remain to it. Handles are in the Show and Eq classes. -- The string produced by showing a handle is system dependent; it should -- include enough information to identify the handle for debugging. A -- handle is equal according to == only to itself; no attempt is -- made to compare the internal state of different handles for equality. data Handle -- | 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: -- -- -- -- An implementation is free to flush the buffer more frequently, but not -- less frequently, than specified above. The output buffer is emptied as -- soon as it has been written out. -- -- Similarly, input occurs according to the buffer mode for the handle: -- -- -- -- The default buffering mode when a handle is opened is -- implementation-dependent and may depend on the file system object -- which is attached to that handle. For most implementations, physical -- files will normally be block-buffered and terminals will normally be -- line-buffered. data BufferMode -- | buffering is disabled if possible. NoBuffering :: BufferMode -- | line-buffering should be enabled if possible. LineBuffering :: BufferMode -- | block-buffering should be enabled if possible. The size of the buffer -- is n items if the argument is Just n and is -- otherwise implementation-dependent. BlockBuffering :: (Maybe Int) -> BufferMode -- | makes a new Handle mkFileHandle :: (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> IOMode -> Maybe TextEncoding -> NewlineMode -> IO Handle -- | like mkFileHandle, except that a Handle is created with -- two independent buffers, one for reading and one for writing. Used for -- full-duplex streams, such as network sockets. mkDuplexHandle :: (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle -- | 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 -- | Computation hLookAhead returns the next character from the -- handle without removing it from the input buffer, blocking until a -- character is available. -- -- This operation may fail with: -- -- hLookAhead :: Handle -> IO Char -- | Computation hSetBuffering hdl mode sets the mode of -- buffering for handle hdl on subsequent reads and writes. -- -- If the buffer mode is changed from BlockBuffering or -- LineBuffering to NoBuffering, then -- -- -- -- This operation may fail with: -- -- hSetBuffering :: Handle -> BufferMode -> IO () -- | 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 () -- | The action hSetEncoding hdl encoding changes -- the text encoding for the handle hdl to encoding. -- The default encoding when a Handle is created is -- localeEncoding, namely the default encoding for the current -- locale. -- -- To create a Handle with no encoding at all, use -- openBinaryFile. To stop further encoding or decoding on an -- existing Handle, use hSetBinaryMode. -- -- hSetEncoding may need to flush buffered data in order to change -- the encoding. hSetEncoding :: Handle -> TextEncoding -> IO () -- | Return the current TextEncoding for the specified -- Handle, or Nothing if the Handle is in binary -- mode. -- -- Note that the TextEncoding remembers nothing about the state of -- the encoder/decoder in use on this Handle. For example, if the -- encoding in use is UTF-16, then using hGetEncoding and -- hSetEncoding to save and restore the encoding may result in an -- extra byte-order-mark being written to the file. hGetEncoding :: Handle -> IO (Maybe TextEncoding) -- | The action hFlush hdl causes any items buffered for -- output in handle hdl to be sent immediately to the operating -- system. -- -- This operation may fail with: -- -- hFlush :: Handle -> IO () -- | The action hFlushAll hdl flushes all buffered data in -- hdl, including any buffered read data. Buffered read data is -- flushed by seeking the file position back to the point before the -- bufferred data was read, and hence only works if hdl is -- seekable (see hIsSeekable). -- -- This operation may fail with: -- -- hFlushAll :: Handle -> IO () -- | Returns a duplicate of the original handle, with its own buffer. The -- two Handles will share a file pointer, however. The original handle's -- buffer is flushed, including discarding any input data, before the -- handle is duplicated. hDuplicate :: Handle -> IO Handle -- | Makes the second handle a duplicate of the first handle. The second -- handle will be closed first, if it is not already. -- -- This can be used to retarget the standard Handles, for example: -- --
--   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) -- | Indicates a mode in which a file should be locked. data LockMode SharedLock :: LockMode ExclusiveLock :: LockMode -- | If a Handle references a file descriptor, attempt to lock -- contents of the underlying file in appropriate mode. If the file is -- already locked in incompatible mode, this function blocks until the -- lock is established. The lock is automatically released upon closing a -- Handle. -- -- Things to be aware of: -- -- 1) This function may block inside a C call. If it does, in order to be -- able to interrupt it with asynchronous exceptions and/or for other -- threads to continue working, you MUST use threaded version of the -- runtime system. -- -- 2) The implementation uses LockFileEx on Windows and -- flock otherwise, hence all of their caveats also apply here. -- -- 3) On non-Windows plaftorms that don't support flock (e.g. -- Solaris) this function throws FileLockingNotImplemented. We -- deliberately choose to not provide fcntl based locking instead because -- of its broken semantics. hLock :: Handle -> LockMode -> IO () -- | Non-blocking version of hLock. hTryLock :: Handle -> LockMode -> IO Bool 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: -- -- hSetPosn :: HandlePosn -> IO () -- | 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 -- | Computation hSeek hdl mode i sets the position of -- handle hdl depending on mode. The offset i -- is given in terms of 8-bit bytes. -- -- If hdl is block- or line-buffered, then seeking to a position -- which is not in the current buffer will first cause any items in the -- output buffer to be written to the device, and then cause the input -- buffer to be discarded. Some handles may not be seekable (see -- hIsSeekable), or only support a subset of the possible -- positioning operations (for instance, it may only be possible to seek -- to the end of a tape, or to a positive offset from the beginning or -- current position). It is not possible to set a negative I/O position, -- or for a physical file, an I/O position beyond the current -- end-of-file. -- -- This operation may fail with: -- -- hSeek :: Handle -> SeekMode -> Integer -> IO () -- | Computation hTell hdl returns the current position of -- the handle hdl, as the number of bytes from the beginning of -- the file. The value returned may be subsequently passed to -- hSeek to reposition the handle to the current position. -- -- This operation may fail with: -- -- hTell :: Handle -> IO Integer hIsOpen :: Handle -> IO Bool hIsClosed :: Handle -> IO Bool hIsReadable :: Handle -> IO Bool hIsWritable :: Handle -> IO Bool -- | Computation hGetBuffering hdl returns the current -- buffering mode for hdl. hGetBuffering :: Handle -> IO BufferMode hIsSeekable :: Handle -> IO Bool -- | Set the echoing status of a handle connected to a terminal. hSetEcho :: Handle -> Bool -> IO () -- | Get the echoing status of a handle connected to a terminal. hGetEcho :: Handle -> IO Bool -- | Is the handle connected to a terminal? hIsTerminalDevice :: Handle -> IO Bool -- | Set the NewlineMode on the specified Handle. All -- buffered data is flushed first. hSetNewlineMode :: Handle -> NewlineMode -> IO () -- | The representation of a newline in the external file or stream. data Newline -- | '\n' LF :: Newline -- | '\r\n' CRLF :: Newline -- | Specifies the translation, if any, of newline characters between -- internal Strings and the external file or stream. Haskell Strings are -- assumed to represent newlines with the '\n' character; the newline -- mode specifies how to translate '\n' on output, and what to translate -- into '\n' on input. data NewlineMode NewlineMode :: Newline -> Newline -> NewlineMode -- | the representation of newlines on input [inputNL] :: NewlineMode -> Newline -- | the representation of newlines on output [outputNL] :: NewlineMode -> Newline -- | The native newline representation for the current platform: LF -- on Unix systems, CRLF on Windows. nativeNewline :: Newline -- | Do no newline translation at all. -- --
--   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: -- -- -- -- NOTE for GHC users: unless you use the -threaded flag, -- hWaitForInput hdl t where t >= 0 will block all -- other Haskell threads for the duration of the call. It behaves like a -- safe foreign call in this respect. hWaitForInput :: Handle -> Int -> IO Bool -- | Computation hGetChar hdl reads a character from the -- file or channel managed by hdl, blocking until a character is -- available. -- -- This operation may fail with: -- -- hGetChar :: Handle -> IO Char -- | Computation hGetLine hdl reads a line from the file or -- channel managed by hdl. -- -- This operation may fail with: -- -- -- -- If hGetLine encounters end-of-file at any other point while -- reading in a line, it is treated as a line terminator and the -- (partial) line is returned. hGetLine :: Handle -> IO String -- | Computation hGetContents hdl returns the list of -- characters corresponding to the unread portion of the channel or file -- managed by hdl, which is put into an intermediate state, -- semi-closed. In this state, hdl is effectively closed, -- but items are read from hdl on demand and accumulated in a -- special list returned by hGetContents hdl. -- -- Any operation that fails because a handle is closed, also fails if a -- handle is semi-closed. The only exception is hClose. A -- semi-closed handle becomes closed: -- -- -- -- Once a semi-closed handle becomes closed, the contents of the -- associated list becomes fixed. The contents of this final list is only -- partially specified: it will contain at least all the items of the -- stream that were evaluated prior to the handle becoming closed. -- -- Any I/O errors encountered while a handle is semi-closed are simply -- discarded. -- -- This operation may fail with: -- -- hGetContents :: Handle -> IO String -- | Computation hPutChar hdl ch writes the character -- ch to the file or channel managed by hdl. Characters -- may be buffered if buffering is enabled for hdl. -- -- This operation may fail with: -- -- hPutChar :: Handle -> Char -> IO () -- | Computation hPutStr hdl s writes the string s -- to the file or channel managed by hdl. -- -- This operation may fail with: -- -- hPutStr :: Handle -> String -> IO () -- | hGetBuf hdl buf count reads data from the handle -- hdl into the buffer buf until either EOF is reached -- or count 8-bit bytes have been read. It returns the number of -- bytes actually read. This may be zero if EOF was reached before any -- data was read (or if count is zero). -- -- hGetBuf never raises an EOF exception, instead it returns a -- value smaller than count. -- -- If the handle is a pipe or socket, and the writing end is closed, -- hGetBuf will behave as if EOF was reached. -- -- hGetBuf ignores the prevailing TextEncoding and -- NewlineMode on the Handle, and reads bytes directly. hGetBuf :: Handle -> Ptr a -> Int -> IO Int -- | hGetBufNonBlocking hdl buf count reads data from the -- handle hdl into the buffer buf until either EOF is -- reached, or count 8-bit bytes have been read, or there is no -- more data available to read immediately. -- -- hGetBufNonBlocking is identical to hGetBuf, except that -- it will never block waiting for data to become available, instead it -- returns only whatever data is available. To wait for data to arrive -- before calling hGetBufNonBlocking, use hWaitForInput. -- -- If the handle is a pipe or socket, and the writing end is closed, -- hGetBufNonBlocking will behave as if EOF was reached. -- -- hGetBufNonBlocking ignores the prevailing TextEncoding -- and NewlineMode on the Handle, and reads bytes directly. -- -- NOTE: on Windows, this function does not work correctly; it behaves -- identically to hGetBuf. hGetBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int -- | 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: -- -- hPutBuf :: Handle -> Ptr a -> Int -> IO () hPutBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int instance GHC.Classes.Eq GHC.IO.Handle.HandlePosn instance GHC.Show.Show GHC.IO.Handle.HandlePosn -- | The standard IO library. module System.IO -- | A value of type IO a is a computation which, when -- performed, does some I/O before returning a value of type a. -- -- There is really only one way to "perform" an I/O action: bind it to -- Main.main in your program. When your program is run, the I/O -- will be performed. It isn't possible to perform I/O from an arbitrary -- function, unless that function is itself in the IO monad and -- called at some point, directly or indirectly, from Main.main. -- -- IO is a monad, so IO actions can be combined using -- either the do-notation or the >> and >>= -- operations from the Monad class. data IO a :: * -> * fixIO :: (a -> IO a) -> IO a -- | 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 -- | Haskell defines operations to read and write characters from and to -- files, represented by values of type Handle. Each value of -- this type is a handle: a record used by the Haskell run-time -- system to manage I/O with file system objects. A handle has at -- least the following properties: -- -- -- -- Most handles will also have a current I/O position indicating where -- the next input or output operation will occur. A handle is -- readable if it manages only input or both input and output; -- likewise, it is writable if it manages only output or both -- input and output. A handle is open when first allocated. Once -- it is closed it can no longer be used for either input or output, -- though an implementation cannot re-use its storage while references -- remain to it. Handles are in the Show and Eq classes. -- The string produced by showing a handle is system dependent; it should -- include enough information to identify the handle for debugging. A -- handle is equal according to == only to itself; no attempt is -- made to compare the internal state of different handles for equality. data Handle -- | A handle managing input from the Haskell program's standard input -- channel. stdin :: Handle -- | A handle managing output to the Haskell program's standard output -- channel. stdout :: Handle -- | A handle managing output to the Haskell program's standard error -- channel. stderr :: Handle -- | withFile name mode act opens a file using -- openFile and passes the resulting handle to the computation -- act. The handle will be closed on exit from withFile, -- whether by normal termination or by raising an exception. If closing -- the handle raises an exception, then this exception will be raised by -- withFile rather than any exception raised by act. withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r -- | Computation openFile file mode allocates and returns a -- new, open handle to manage the file file. It manages input if -- mode is ReadMode, output if mode is -- WriteMode or AppendMode, and both input and output if -- mode is ReadWriteMode. -- -- If the file does not exist and it is opened for output, it should be -- created as a new file. If mode is WriteMode and the -- file already exists, then it should be truncated to zero length. Some -- operating systems delete empty files, so there is no guarantee that -- the file will exist following an openFile with mode -- WriteMode unless it is subsequently written to successfully. -- The handle is positioned at the end of the file if mode is -- AppendMode, and otherwise at the beginning (in which case its -- internal position is 0). The initial buffer mode is -- implementation-dependent. -- -- This operation may fail with: -- -- -- -- Note: if you will be working with files containing binary data, you'll -- want to be using openBinaryFile. openFile :: FilePath -> IOMode -> IO Handle -- | See openFile data IOMode ReadMode :: IOMode WriteMode :: IOMode AppendMode :: IOMode ReadWriteMode :: IOMode -- | 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 () -- | 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 () -- | 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: -- -- -- -- An implementation is free to flush the buffer more frequently, but not -- less frequently, than specified above. The output buffer is emptied as -- soon as it has been written out. -- -- Similarly, input occurs according to the buffer mode for the handle: -- -- -- -- The default buffering mode when a handle is opened is -- implementation-dependent and may depend on the file system object -- which is attached to that handle. For most implementations, physical -- files will normally be block-buffered and terminals will normally be -- line-buffered. data BufferMode -- | buffering is disabled if possible. NoBuffering :: BufferMode -- | line-buffering should be enabled if possible. LineBuffering :: BufferMode -- | block-buffering should be enabled if possible. The size of the buffer -- is n items if the argument is Just n and is -- otherwise implementation-dependent. BlockBuffering :: (Maybe Int) -> BufferMode -- | Computation hSetBuffering hdl mode sets the mode of -- buffering for handle hdl on subsequent reads and writes. -- -- If the buffer mode is changed from BlockBuffering or -- LineBuffering to NoBuffering, then -- -- -- -- This operation may fail with: -- -- hSetBuffering :: Handle -> BufferMode -> IO () -- | Computation hGetBuffering hdl returns the current -- buffering mode for hdl. hGetBuffering :: Handle -> IO BufferMode -- | The action hFlush hdl causes any items buffered for -- output in handle hdl to be sent immediately to the operating -- system. -- -- This operation may fail with: -- -- hFlush :: Handle -> IO () -- | 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: -- -- hSetPosn :: HandlePosn -> IO () data HandlePosn -- | Computation hSeek hdl mode i sets the position of -- handle hdl depending on mode. The offset i -- is given in terms of 8-bit bytes. -- -- If hdl is block- or line-buffered, then seeking to a position -- which is not in the current buffer will first cause any items in the -- output buffer to be written to the device, and then cause the input -- buffer to be discarded. Some handles may not be seekable (see -- hIsSeekable), or only support a subset of the possible -- positioning operations (for instance, it may only be possible to seek -- to the end of a tape, or to a positive offset from the beginning or -- current position). It is not possible to set a negative I/O position, -- or for a physical file, an I/O position beyond the current -- end-of-file. -- -- This operation may fail with: -- -- hSeek :: Handle -> SeekMode -> Integer -> IO () -- | 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 -- | Computation hTell hdl returns the current position of -- the handle hdl, as the number of bytes from the beginning of -- the file. The value returned may be subsequently passed to -- hSeek to reposition the handle to the current position. -- -- This operation may fail with: -- -- hTell :: Handle -> IO Integer hIsOpen :: Handle -> IO Bool hIsClosed :: Handle -> IO Bool hIsReadable :: Handle -> IO Bool hIsWritable :: Handle -> IO Bool hIsSeekable :: Handle -> IO Bool -- | Is the handle connected to a terminal? hIsTerminalDevice :: Handle -> IO Bool -- | Set the echoing status of a handle connected to a terminal. hSetEcho :: Handle -> Bool -> IO () -- | Get the echoing status of a handle connected to a terminal. hGetEcho :: Handle -> IO Bool -- | 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: -- -- -- -- NOTE for GHC users: unless you use the -threaded flag, -- hWaitForInput hdl t where t >= 0 will block all -- other Haskell threads for the duration of the call. It behaves like a -- safe foreign call in this respect. hWaitForInput :: Handle -> Int -> IO Bool -- | Computation hReady hdl indicates whether at least one -- item is available for input from handle hdl. -- -- This operation may fail with: -- -- hReady :: Handle -> IO Bool -- | Computation hGetChar hdl reads a character from the -- file or channel managed by hdl, blocking until a character is -- available. -- -- This operation may fail with: -- -- hGetChar :: Handle -> IO Char -- | Computation hGetLine hdl reads a line from the file or -- channel managed by hdl. -- -- This operation may fail with: -- -- -- -- If hGetLine encounters end-of-file at any other point while -- reading in a line, it is treated as a line terminator and the -- (partial) line is returned. hGetLine :: Handle -> IO String -- | Computation hLookAhead returns the next character from the -- handle without removing it from the input buffer, blocking until a -- character is available. -- -- This operation may fail with: -- -- hLookAhead :: Handle -> IO Char -- | Computation hGetContents hdl returns the list of -- characters corresponding to the unread portion of the channel or file -- managed by hdl, which is put into an intermediate state, -- semi-closed. In this state, hdl is effectively closed, -- but items are read from hdl on demand and accumulated in a -- special list returned by hGetContents hdl. -- -- Any operation that fails because a handle is closed, also fails if a -- handle is semi-closed. The only exception is hClose. A -- semi-closed handle becomes closed: -- -- -- -- Once a semi-closed handle becomes closed, the contents of the -- associated list becomes fixed. The contents of this final list is only -- partially specified: it will contain at least all the items of the -- stream that were evaluated prior to the handle becoming closed. -- -- Any I/O errors encountered while a handle is semi-closed are simply -- discarded. -- -- This operation may fail with: -- -- hGetContents :: Handle -> IO String -- | Computation hPutChar hdl ch writes the character -- ch to the file or channel managed by hdl. Characters -- may be buffered if buffering is enabled for hdl. -- -- This operation may fail with: -- -- hPutChar :: Handle -> Char -> IO () -- | Computation hPutStr hdl s writes the string s -- to the file or channel managed by hdl. -- -- This operation may fail with: -- -- hPutStr :: Handle -> String -> IO () -- | The same as hPutStr, but adds a newline character. hPutStrLn :: Handle -> String -> IO () -- | Computation hPrint hdl t writes the string -- representation of t given by the shows function to the -- file or channel managed by hdl and appends a newline. -- -- This operation may fail with: -- -- hPrint :: Show a => Handle -> a -> IO () -- | 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 () -- | Write a character to the standard output device (same as -- hPutChar stdout). putChar :: Char -> IO () -- | Write a string to the standard output device (same as hPutStr -- stdout). putStr :: String -> IO () -- | The same as putStr, but adds a newline character. putStrLn :: String -> IO () -- | The print function outputs a value of any printable type to the -- standard output device. Printable types are those that are instances -- of class Show; print converts values to strings for -- output using the show operation and adds a newline. -- -- For example, a program to print the first 20 integers and their powers -- of 2 could be written as: -- --
--   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: -- -- hPutBuf :: Handle -> Ptr a -> Int -> IO () -- | hGetBuf hdl buf count reads data from the handle -- hdl into the buffer buf until either EOF is reached -- or count 8-bit bytes have been read. It returns the number of -- bytes actually read. This may be zero if EOF was reached before any -- data was read (or if count is zero). -- -- hGetBuf never raises an EOF exception, instead it returns a -- value smaller than count. -- -- If the handle is a pipe or socket, and the writing end is closed, -- hGetBuf will behave as if EOF was reached. -- -- hGetBuf ignores the prevailing TextEncoding and -- NewlineMode on the Handle, and reads bytes directly. hGetBuf :: Handle -> Ptr a -> Int -> IO Int -- | hGetBufSome hdl buf count reads data from the handle -- hdl into the buffer buf. If there is any data -- available to read, then hGetBufSome returns it immediately; it -- only blocks if there is no data to be read. -- -- It returns the number of bytes actually read. This may be zero if EOF -- was reached before any data was read (or if count is zero). -- -- hGetBufSome never raises an EOF exception, instead it returns a -- value smaller than count. -- -- If the handle is a pipe or socket, and the writing end is closed, -- hGetBufSome will behave as if EOF was reached. -- -- hGetBufSome ignores the prevailing TextEncoding and -- NewlineMode on the Handle, and reads bytes directly. hGetBufSome :: Handle -> Ptr a -> Int -> IO Int hPutBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int -- | hGetBufNonBlocking hdl buf count reads data from the -- handle hdl into the buffer buf until either EOF is -- reached, or count 8-bit bytes have been read, or there is no -- more data available to read immediately. -- -- hGetBufNonBlocking is identical to hGetBuf, except that -- it will never block waiting for data to become available, instead it -- returns only whatever data is available. To wait for data to arrive -- before calling hGetBufNonBlocking, use hWaitForInput. -- -- If the handle is a pipe or socket, and the writing end is closed, -- hGetBufNonBlocking will behave as if EOF was reached. -- -- hGetBufNonBlocking ignores the prevailing TextEncoding -- and NewlineMode on the Handle, and reads bytes directly. -- -- NOTE: on Windows, this function does not work correctly; it behaves -- identically to hGetBuf. hGetBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int -- | The function creates a temporary file in ReadWrite mode. The created -- file isn't deleted automatically, so you need to delete it manually. -- -- The file is created with permissions such that only the current user -- can read/write it. -- -- With some exceptions (see below), the file will be created securely in -- the sense that an attacker should not be able to cause openTempFile to -- overwrite another file on the filesystem using your credentials, by -- putting symbolic links (on Unix) in the place where the temporary file -- is to be created. On Unix the O_CREAT and O_EXCL -- flags are used to prevent this attack, but note that O_EXCL -- is sometimes not supported on NFS filesystems, so if you rely on this -- behaviour it is best to use local filesystems only. openTempFile :: FilePath -> String -> IO (FilePath, Handle) -- | Like openTempFile, but opens the file in binary mode. See -- openBinaryFile for more comments. openBinaryTempFile :: FilePath -> String -> IO (FilePath, Handle) -- | Like openTempFile, but uses the default file permissions openTempFileWithDefaultPermissions :: FilePath -> String -> IO (FilePath, Handle) -- | Like openBinaryTempFile, but uses the default file permissions openBinaryTempFileWithDefaultPermissions :: FilePath -> String -> IO (FilePath, Handle) -- | The action hSetEncoding hdl encoding changes -- the text encoding for the handle hdl to encoding. -- The default encoding when a Handle is created is -- localeEncoding, namely the default encoding for the current -- locale. -- -- To create a Handle with no encoding at all, use -- openBinaryFile. To stop further encoding or decoding on an -- existing Handle, use hSetBinaryMode. -- -- hSetEncoding may need to flush buffered data in order to change -- the encoding. hSetEncoding :: Handle -> TextEncoding -> IO () -- | Return the current TextEncoding for the specified -- Handle, or Nothing if the Handle is in binary -- mode. -- -- Note that the TextEncoding remembers nothing about the state of -- the encoder/decoder in use on this Handle. For example, if the -- encoding in use is UTF-16, then using hGetEncoding and -- hSetEncoding to save and restore the encoding may result in an -- extra byte-order-mark being written to the file. hGetEncoding :: Handle -> IO (Maybe TextEncoding) -- | 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 -- | 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 -- | 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 -- | The Unicode encoding of the current locale -- -- This is the initial locale encoding: if it has been subsequently -- changed by setLocaleEncoding this value will not reflect that -- change. localeEncoding :: TextEncoding -- | 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 -- -- -- -- The set of known encodings is system-dependent, but includes at least: -- -- -- -- There is additional notation (borrowed from GNU iconv) for specifying -- how illegal characters are handled: -- -- -- -- In theory, this mechanism allows arbitrary data to be roundtripped via -- a String with no loss of data. In practice, there are two -- limitations to be aware of: -- --
    --
  1. This only stands a chance of working for an encoding which is an -- ASCII superset, as for security reasons we refuse to escape any bytes -- smaller than 128. Many encodings of interest are ASCII supersets (in -- particular, you can assume that the locale encoding is an ASCII -- superset) but many (such as UTF-16) are not.
  2. --
  3. If the underlying encoding is not itself roundtrippable, this -- mechanism can fail. Roundtrippable encodings are those which have an -- injective mapping into Unicode. Almost all encodings meet this -- criteria, but some do not. Notably, Shift-JIS (CP932) and Big5 contain -- several different encodings of the same Unicode codepoint.
  4. --
-- -- On Windows, you can access supported code pages with the prefix -- CP; for example, "CP1250". mkTextEncoding :: String -> IO TextEncoding -- | Set the NewlineMode on the specified Handle. All -- buffered data is flushed first. hSetNewlineMode :: Handle -> NewlineMode -> IO () -- | The representation of a newline in the external file or stream. data Newline -- | '\n' LF :: Newline -- | '\r\n' CRLF :: Newline -- | The native newline representation for the current platform: LF -- on Unix systems, CRLF on Windows. nativeNewline :: Newline -- | Specifies the translation, if any, of newline characters between -- internal Strings and the external file or stream. Haskell Strings are -- assumed to represent newlines with the '\n' character; the newline -- mode specifies how to translate '\n' on output, and what to translate -- into '\n' on input. data NewlineMode NewlineMode :: Newline -> Newline -> NewlineMode -- | the representation of newlines on input [inputNL] :: NewlineMode -> Newline -- | the representation of newlines on output [outputNL] :: NewlineMode -> Newline -- | Do no newline translation at all. -- --
--   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 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 -- | Computes the hash of a given file. This function loops over the -- handle, running in constant memory. getFileHash :: FilePath -> IO Fingerprint -- | Monadic fixpoints. -- -- For a detailed discussion, see Levent Erkok's thesis, Value -- Recursion in Monadic Computations, Oregon Graduate Institute, -- 2002. module Control.Monad.Fix -- | Monads having fixed points with a 'knot-tying' semantics. Instances of -- MonadFix should satisfy the following laws: -- -- -- -- This class is used in the translation of the recursive do -- notation supported by GHC and Hugs. class (Monad m) => MonadFix m -- | The fixed point of a monadic computation. mfix f -- executes the action f only once, with the eventual output fed -- back as the input. Hence f should not be strict, for then -- mfix f would diverge. mfix :: MonadFix m => (a -> m a) -> m a -- | 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 instance Control.Monad.Fix.MonadFix GHC.Base.Maybe instance Control.Monad.Fix.MonadFix [] instance Control.Monad.Fix.MonadFix GHC.Types.IO instance Control.Monad.Fix.MonadFix ((->) r) instance Control.Monad.Fix.MonadFix (Data.Either.Either e) instance Control.Monad.Fix.MonadFix (GHC.ST.ST s) instance Control.Monad.Fix.MonadFix Data.Monoid.Dual instance Control.Monad.Fix.MonadFix Data.Monoid.Sum instance Control.Monad.Fix.MonadFix Data.Monoid.Product instance Control.Monad.Fix.MonadFix Data.Monoid.First instance Control.Monad.Fix.MonadFix Data.Monoid.Last instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (Data.Monoid.Alt f) instance Control.Monad.Fix.MonadFix GHC.Generics.Par1 instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (GHC.Generics.Rec1 f) instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (GHC.Generics.M1 i c f) instance (Control.Monad.Fix.MonadFix f, Control.Monad.Fix.MonadFix g) => Control.Monad.Fix.MonadFix (f GHC.Generics.:*: g) -- | The identity functor and monad. -- -- This trivial type constructor serves two purposes: -- -- module Data.Functor.Identity -- | Identity functor and monad. (a non-strict monad) newtype Identity a Identity :: a -> Identity a [runIdentity] :: Identity a -> a instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Data.Functor.Identity.Identity a) instance GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Identity.Identity a) instance GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Identity.Identity a) instance GHC.Real.Real a => GHC.Real.Real (Data.Functor.Identity.Identity a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Functor.Identity.Identity a) instance GHC.Num.Num a => GHC.Num.Num (Data.Functor.Identity.Identity a) instance GHC.Base.Monoid a => GHC.Base.Monoid (Data.Functor.Identity.Identity a) instance GHC.Arr.Ix a => GHC.Arr.Ix (Data.Functor.Identity.Identity a) instance GHC.Real.Integral a => GHC.Real.Integral (Data.Functor.Identity.Identity a) instance GHC.Generics.Generic1 Data.Functor.Identity.Identity instance GHC.Generics.Generic (Data.Functor.Identity.Identity a) instance GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Identity.Identity a) instance GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Identity.Identity a) instance Data.Bits.FiniteBits a => Data.Bits.FiniteBits (Data.Functor.Identity.Identity a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Functor.Identity.Identity a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Functor.Identity.Identity a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Functor.Identity.Identity a) instance Data.Bits.Bits a => Data.Bits.Bits (Data.Functor.Identity.Identity a) instance GHC.Read.Read a => GHC.Read.Read (Data.Functor.Identity.Identity a) instance GHC.Show.Show a => GHC.Show.Show (Data.Functor.Identity.Identity a) instance Data.Foldable.Foldable Data.Functor.Identity.Identity instance GHC.Base.Functor Data.Functor.Identity.Identity instance GHC.Base.Applicative Data.Functor.Identity.Identity instance GHC.Base.Monad Data.Functor.Identity.Identity instance Control.Monad.Fix.MonadFix Data.Functor.Identity.Identity -- | Basic arrow definitions, based on -- -- -- -- plus a couple of definitions (returnA and loop) from -- -- -- -- These papers and more information on arrows can be found at -- http://www.haskell.org/arrows/. module Control.Arrow -- | The basic arrow class. -- -- Instances should satisfy the following laws: -- -- -- -- where -- --
--   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 -- | Lift a function to an arrow. arr :: Arrow a => (b -> c) -> a b c -- | Send the first component of the input through the argument arrow, and -- copy the rest unchanged to the output. first :: Arrow a => a b c -> a (b, d) (c, d) -- | A mirror image of first. -- -- The default definition may be overridden with a more efficient version -- if desired. second :: Arrow a => a b c -> a (d, b) (d, c) -- | Split the input between the two argument arrows and combine their -- output. Note that this is in general not a functor. -- -- The default definition may be overridden with a more efficient version -- if desired. (***) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c') -- | Fanout: send the input to both argument arrows and combine their -- output. -- -- The default definition may be overridden with a more efficient version -- if desired. (&&&) :: 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 infixr 1 ^>> -- | Postcomposition with a pure function. (>>^) :: Arrow a => a b c -> (c -> d) -> a b d infixr 1 >>^ -- | Left-to-right composition (>>>) :: Category cat => cat a b -> cat b c -> cat a c infixr 1 >>> -- | Right-to-left composition (<<<) :: Category cat => cat b c -> cat a b -> cat a c infixr 1 <<< -- | Precomposition with a pure function (right-to-left variant). (<<^) :: Arrow a => a c d -> (b -> c) -> a b d infixr 1 <<^ -- | Postcomposition with a pure function (right-to-left variant). (^<<) :: Arrow a => (c -> d) -> a b c -> a b d infixr 1 ^<< class Arrow a => ArrowZero a zeroArrow :: ArrowZero a => a b c -- | A monoid on arrows. class ArrowZero a => ArrowPlus a -- | An associative operation with identity zeroArrow. (<+>) :: 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. -- -- Instances should satisfy the following laws: -- -- -- -- where -- --
--   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 -- | Feed marked inputs through the argument arrow, passing the rest -- through unchanged to the output. left :: ArrowChoice a => a b c -> a (Either b d) (Either c d) -- | A mirror image of left. -- -- The default definition may be overridden with a more efficient version -- if desired. right :: ArrowChoice a => a b c -> a (Either d b) (Either d c) -- | Split the input between the two argument arrows, retagging and merging -- their outputs. Note that this is in general not a functor. -- -- The default definition may be overridden with a more efficient version -- if desired. (+++) :: ArrowChoice a => a b c -> a b' c' -> a (Either b b') (Either c c') -- | Fanin: Split the input between the two argument arrows and merge their -- outputs. -- -- The default definition may be overridden with a more efficient version -- if desired. (|||) :: 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: -- -- -- -- Such arrows are equivalent to monads (see ArrowMonad). class Arrow a => ArrowApply a app :: ArrowApply a => a (a b c, b) c -- | The ArrowApply class is equivalent to Monad: any monad -- gives rise to a Kleisli arrow, and any instance of -- ArrowApply defines a monad. newtype ArrowMonad a b ArrowMonad :: (a () b) -> ArrowMonad a b -- | Any instance of ArrowApply can be made into an instance of -- ArrowChoice by defining left = leftApp. leftApp :: ArrowApply a => a b c -> a (Either b d) (Either c d) -- | The loop operator expresses computations in which an output -- value is fed back as input, although the computation occurs only once. -- It underlies the rec value recursion construct in arrow -- notation. loop should satisfy the following laws: -- -- -- -- where -- --
--   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 Control.Arrow.ArrowLoop (->) instance Control.Monad.Fix.MonadFix m => Control.Arrow.ArrowLoop (Control.Arrow.Kleisli m) instance Control.Arrow.Arrow a => GHC.Base.Functor (Control.Arrow.ArrowMonad a) instance Control.Arrow.Arrow a => GHC.Base.Applicative (Control.Arrow.ArrowMonad a) instance Control.Arrow.ArrowApply a => GHC.Base.Monad (Control.Arrow.ArrowMonad a) instance Control.Arrow.ArrowPlus a => GHC.Base.Alternative (Control.Arrow.ArrowMonad a) instance (Control.Arrow.ArrowApply a, Control.Arrow.ArrowPlus a) => GHC.Base.MonadPlus (Control.Arrow.ArrowMonad a) instance Control.Arrow.ArrowApply (->) instance GHC.Base.Monad m => Control.Arrow.ArrowApply (Control.Arrow.Kleisli m) instance Control.Arrow.ArrowChoice (->) instance GHC.Base.Monad m => Control.Arrow.ArrowChoice (Control.Arrow.Kleisli m) instance GHC.Base.MonadPlus m => Control.Arrow.ArrowPlus (Control.Arrow.Kleisli m) instance GHC.Base.MonadPlus m => Control.Arrow.ArrowZero (Control.Arrow.Kleisli m) instance GHC.Base.Monad m => Control.Category.Category (Control.Arrow.Kleisli m) instance GHC.Base.Monad m => Control.Arrow.Arrow (Control.Arrow.Kleisli m) instance Control.Arrow.Arrow (->) -- | 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 -- -- -- -- This interface was introduced for parsers by Niklas Röjemo, because it -- admits more sharing than the monadic interface. The names here are -- mostly based on parsing work by Doaitse Swierstra. -- -- For more details, see Applicative Programming with Effects, by -- Conor McBride and Ross Paterson. module Control.Applicative -- | A functor with application, providing operations to -- -- -- -- A minimal complete definition must include implementations of -- pure and of either <*> or liftA2. If it -- defines both, then they must behave the same as their default -- definitions: -- -- (<*>) = liftA2 id -- liftA2 f x y = f <$> x <*> -- y -- -- Further, any definition must satisfy the following: -- -- -- -- The other methods have the following default definitions, which may be -- overridden with equivalent specialized implementations: -- -- -- -- As a consequence of these laws, the Functor instance for -- f will satisfy -- -- -- -- It may be useful to note that supposing -- --
--   forall x y. p (q x y) = f x . g y
--   
-- -- it follows from the above that -- --
--   liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v
--   
-- -- If f is also a Monad, it should satisfy -- -- -- -- (which implies that pure and <*> satisfy the -- applicative functor laws). class Functor f => Applicative f -- | Lift a value. pure :: Applicative f => a -> f a -- | Sequential application. -- -- A few functors support an implementation of <*> that is -- more efficient than the default one. (<*>) :: Applicative f => f (a -> b) -> f a -> f b -- | Lift a binary function to actions. -- -- Some functors support an implementation of liftA2 that is more -- efficient than the default one. In particular, if fmap is an -- expensive operation, it is likely better to use liftA2 than to -- fmap over the structure and then use <*>. liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c -- | Sequence actions, discarding the value of the first argument. (*>) :: Applicative f => f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. (<*) :: Applicative f => f a -> f b -> f a -- | A monoid on applicative functors. -- -- If defined, some and many should be the least solutions -- of the equations: -- -- class Applicative f => Alternative f -- | The identity of <|> empty :: Alternative f => f a -- | An associative binary operation (<|>) :: Alternative f => f a -> f a -> f a -- | One or more. some :: Alternative f => f a -> f [a] -- | Zero or more. many :: Alternative f => f a -> f [a] -- | The Const functor. 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. newtype ZipList a ZipList :: [a] -> ZipList a [getZipList] :: ZipList a -> [a] -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
--    ($)  ::              (a -> b) ->   a ->   b
--   (<$>) :: Functor f => (a -> b) -> f a -> f b
--   
-- -- Whereas $ is function application, <$> is -- function application lifted over a Functor. -- --

Examples

-- -- Convert from a Maybe Int to a -- Maybe String using show: -- --
--   >>> show <$> Nothing
--   Nothing
--   
--   >>> show <$> Just 3
--   Just "3"
--   
-- -- Convert from an Either Int Int to -- an Either Int String using -- show: -- --
--   >>> show <$> Left 17
--   Left 17
--   
--   >>> show <$> Right 17
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> (*2) <$> [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> even <$> (2,2)
--   (2,True)
--   
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 <$> -- | 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 infixl 4 <$ -- | A variant of <*> with the arguments reversed. (<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 <**> -- | 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 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 GHC.Generics.Generic1 Control.Applicative.ZipList instance GHC.Generics.Generic (Control.Applicative.ZipList a) instance Data.Foldable.Foldable Control.Applicative.ZipList instance GHC.Base.Functor Control.Applicative.ZipList instance GHC.Read.Read a => GHC.Read.Read (Control.Applicative.ZipList a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Control.Applicative.ZipList a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Control.Applicative.ZipList a) instance GHC.Show.Show a => GHC.Show.Show (Control.Applicative.ZipList a) instance GHC.Generics.Generic1 (Control.Applicative.WrappedArrow a b) instance GHC.Generics.Generic (Control.Applicative.WrappedArrow a b c) instance GHC.Base.Monad m => GHC.Base.Monad (Control.Applicative.WrappedMonad m) instance GHC.Generics.Generic1 (Control.Applicative.WrappedMonad m) instance GHC.Generics.Generic (Control.Applicative.WrappedMonad m a) instance GHC.Base.Applicative Control.Applicative.ZipList instance Control.Arrow.Arrow a => GHC.Base.Functor (Control.Applicative.WrappedArrow a b) instance Control.Arrow.Arrow a => GHC.Base.Applicative (Control.Applicative.WrappedArrow a b) instance (Control.Arrow.ArrowZero a, Control.Arrow.ArrowPlus a) => GHC.Base.Alternative (Control.Applicative.WrappedArrow a b) instance GHC.Base.Monad m => GHC.Base.Functor (Control.Applicative.WrappedMonad m) instance GHC.Base.Monad m => GHC.Base.Applicative (Control.Applicative.WrappedMonad m) instance GHC.Base.MonadPlus m => GHC.Base.Alternative (Control.Applicative.WrappedMonad m) -- | Class of data structures that can be traversed from left to right, -- performing an action on each element. -- -- See also -- -- module Data.Traversable -- | Functors representing data structures that can be traversed from left -- to right. -- -- A definition of traverse must satisfy the following laws: -- -- -- -- A definition of sequenceA must satisfy the following laws: -- -- -- -- where an applicative transformation is a function -- --
--   t :: (Applicative f, Applicative g) => f a -> g a
--   
-- -- preserving the Applicative operations, i.e. -- -- -- -- and the identity functor Identity and composition of functors -- Compose are defined as -- --
--   newtype Identity a = Identity a
--   
--   instance Functor Identity where
--     fmap f (Identity x) = Identity (f x)
--   
--   instance Applicative Identity where
--     pure x = Identity x
--     Identity f <*> Identity x = Identity (f x)
--   
--   newtype Compose f g a = Compose (f (g a))
--   
--   instance (Functor f, Functor g) => Functor (Compose f g) where
--     fmap f (Compose x) = Compose (fmap (fmap f) x)
--   
--   instance (Applicative f, Applicative g) => Applicative (Compose f g) where
--     pure x = Compose (pure (pure x))
--     Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
--   
-- -- (The naturality law is implied by parametricity.) -- -- Instances are similar to Functor, e.g. given a data type -- --
--   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: -- -- class (Functor t, Foldable t) => Traversable t -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and collect the results. For a version that -- ignores the results see traverse_. traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) -- | Evaluate each action in the structure from left to right, and and -- collect the results. For a version that ignores the results see -- sequenceA_. sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a) -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results. For a version -- that ignores the results see mapM_. mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) -- | Evaluate each monadic action in the structure from left to right, and -- collect the results. For a version that ignores the results see -- sequence_. sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) -- | for is traverse with its arguments flipped. For a -- version that ignores the results see for_. for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) -- | forM is mapM with its arguments flipped. For a version -- that ignores the results see forM_. forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) -- | The mapAccumL function behaves like a combination of -- fmap and foldl; it applies a function to each element -- of a structure, passing an accumulating parameter from left to right, -- and returning a final value of this accumulator together with the new -- structure. mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) -- | The mapAccumR function behaves like a combination of -- fmap and foldr; it applies a function to each element -- of a structure, passing an accumulating parameter from right to left, -- and returning a final value of this accumulator together with the new -- structure. mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) -- | This function may be used as a value for fmap in a -- Functor instance, provided that traverse is defined. -- (Using fmapDefault with a Traversable instance defined -- only by sequenceA will result in infinite recursion.) -- --
--   fmapDefault f ≡ runIdentity . traverse (Identity . f)
--   
fmapDefault :: forall t a b. Traversable t => (a -> b) -> t a -> t b -- | This function may be used as a value for foldMap in a -- Foldable instance. -- --
--   foldMapDefault f ≡ getConst . traverse (Const . f)
--   
foldMapDefault :: forall t m a. (Traversable t, Monoid m) => (a -> m) -> t a -> m instance Data.Traversable.Traversable Data.Functor.Identity.Identity instance Data.Traversable.Traversable GHC.Generics.V1 instance Data.Traversable.Traversable GHC.Generics.Par1 instance Data.Traversable.Traversable f => Data.Traversable.Traversable (GHC.Generics.Rec1 f) instance Data.Traversable.Traversable (GHC.Generics.K1 i c) instance Data.Traversable.Traversable f => Data.Traversable.Traversable (GHC.Generics.M1 i c f) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (f GHC.Generics.:+: g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (f GHC.Generics.:*: g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (f GHC.Generics.:.: g) instance Data.Traversable.Traversable (GHC.Generics.URec (GHC.Ptr.Ptr ())) instance Data.Traversable.Traversable (GHC.Generics.URec GHC.Types.Char) instance Data.Traversable.Traversable (GHC.Generics.URec GHC.Types.Double) instance Data.Traversable.Traversable (GHC.Generics.URec GHC.Types.Float) instance Data.Traversable.Traversable (GHC.Generics.URec GHC.Types.Int) instance Data.Traversable.Traversable (GHC.Generics.URec GHC.Types.Word) instance Data.Traversable.Traversable GHC.Base.Maybe instance Data.Traversable.Traversable [] instance Data.Traversable.Traversable (Data.Either.Either a) instance Data.Traversable.Traversable ((,) a) instance GHC.Arr.Ix i => Data.Traversable.Traversable (GHC.Arr.Array i) instance Data.Traversable.Traversable Data.Proxy.Proxy instance Data.Traversable.Traversable (Data.Functor.Const.Const m) instance Data.Traversable.Traversable Data.Monoid.Dual instance Data.Traversable.Traversable Data.Monoid.Sum instance Data.Traversable.Traversable Data.Monoid.Product instance Data.Traversable.Traversable Data.Monoid.First instance Data.Traversable.Traversable Data.Monoid.Last instance Data.Traversable.Traversable Control.Applicative.ZipList instance Data.Traversable.Traversable GHC.Generics.U1 -- | 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] infixr 5 ++ -- | 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] -- | Decompose a list into its head and tail. If the list is empty, returns -- Nothing. If the list is non-empty, returns Just (x, -- xs), where x is the head of the list and xs its -- tail. uncons :: [a] -> Maybe (a, [a]) -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. length :: Foldable t => t 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]]
--   
-- -- If some of the rows are shorter than the following rows, their -- elements are skipped: -- --
--   transpose [[10,11],[20],[],[30,31,32]] == [[10,20,30],[11,31],[32]]
--   
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]] -- | Left-associative fold of a structure. -- -- In the case of lists, foldl, when 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
--   
-- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldl' -- will diverge if given an infinite list. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is -- that latter does not force the "inner" results (e.g. z f -- x1 in the above example) before applying them to the operator -- (e.g. to (f x2)). This results in a thunk chain -- O(n) elements long, which then must be evaluated from the -- outside-in. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldl f z = foldl f z . toList
--   
foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | Left-associative fold of a structure but with strict application of -- the operator. -- -- This ensures that each step of the fold is forced to weak head normal -- form before being applied, avoiding the collection of thunks that -- would otherwise occur. This is often what you want to strictly reduce -- a finite list to a single, monolithic result (e.g. length). -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldl f z = foldl' f z . toList
--   
foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | A variant of foldl that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldl1 f = foldl1 f . toList
--   
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a -- | A strict version of foldl1 foldl1' :: (a -> a -> a) -> [a] -> a -- | Right-associative fold of a structure. -- -- In the case of lists, foldr, when 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)...)
--   
-- -- Note that, since the head of the resulting expression is produced by -- an application of the operator to the first element of the list, -- foldr can produce a terminating expression from an infinite -- list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldr f z = foldr f z . toList
--   
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | A variant of foldr that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldr1 f = foldr1 f . toList
--   
foldr1 :: Foldable t => (a -> a -> a) -> 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 :: forall a. (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure. minimum :: forall a. (Foldable t, Ord a) => t 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 :: (b -> a -> b) -> b -> [a] -> [b] -- | A strictly accumulating version of scanl scanl' :: (b -> a -> b) -> b -> [a] -> [b] -- | 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 -- fmap and foldl; it applies a function to each element -- of a structure, passing an accumulating parameter from left to right, -- and returning a final value of this accumulator together with the new -- structure. mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) -- | The mapAccumR function behaves like a combination of -- fmap and foldr; it applies a function to each element -- of a structure, passing an accumulating parameter from right to left, -- and returning a final value of this accumulator together with the new -- structure. mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) -- | 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 (xs ++ _|_) = inits xs ++ _|_ -- -- In particular, 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. The second list 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 -- | The isSubsequenceOf function takes two lists and returns -- True if all the elements of the first list occur, in order, in -- the second. The elements do not have to occur consecutively. -- -- isSubsequenceOf x y is equivalent to elem x -- (subsequences y). -- --

Examples

-- --
--   >>> isSubsequenceOf "GHC" "The Glorious Haskell Compiler"
--   True
--   
--   >>> isSubsequenceOf ['a','d'..'z'] ['a'..'z']
--   True
--   
--   >>> isSubsequenceOf [1..10] [10,9..0]
--   False
--   
isSubsequenceOf :: (Eq a) => [a] -> [a] -> Bool -- | Does the element occur in the structure? elem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `elem` -- | notElem is the negation of elem. notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `notElem` -- | 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 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 -- | 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 infixl 9 !! -- | 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 is right-lazy: -- --
--   zip [] _|_ = []
--   
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 is right-lazy: -- --
--   zipWith f [] _|_ = []
--   
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. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
--   lines "" == []
--   lines "\n" == [""]
--   lines "one" == ["one"]
--   lines "one\n" == ["one"]
--   lines "one\n\n" == ["one",""]
--   lines "one\ntwo" == ["one","two"]
--   lines "one\ntwo\n" == ["one","two"]
--   
-- -- Thus lines s contains at least as many elements as -- newlines in s. 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] infix 5 \\ -- | 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. If the element is found -- in both the first and the second list, the element from the first list -- will be used. 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. -- -- Elements are arranged from from lowest to highest, keeping duplicates -- in the order they appeared in the input. sort :: (Ord a) => [a] -> [a] -- | Sort a list by comparing the results of a key function applied to each -- element. sortOn f is equivalent to sortBy (comparing -- f), but has the performance advantage of only evaluating -- f once for each element in the input list. This is called the -- decorate-sort-undecorate paradigm, or Schwartzian transform. -- -- Elements are arranged from from lowest to highest, keeping duplicates -- in the order they appeared in the input. sortOn :: Ord b => (a -> b) -> [a] -> [a] -- | The insert function takes an element and a list and inserts the -- element into the list at the first position where it is 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 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 with respect to the given -- comparison function. minimumBy :: Foldable t => (a -> a -> Ordering) -> t 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) => [a] -> 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 -> [a] -> ([a], [a]) -- | The genericIndex function is an overloaded version of -- !!, which accepts any Integral value as the index. genericIndex :: (Integral i) => [a] -> i -> a -- | 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] -- | Functions for tracing and monitoring execution. -- -- These can be useful for investigating bugs or performance problems. -- They should not be used in production code. module Debug.Trace -- | The trace function outputs the trace message given as its first -- argument, before returning the second argument as its result. -- -- For example, this returns the value of f x but first outputs -- the message. -- --
--   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 returns the message instead of a third value. traceId :: String -> String -- | 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 traceShow but returns the shown value instead of a third -- value. traceShowId :: (Show a) => a -> a -- | like trace, but additionally prints a call stack if one is -- available. -- -- In the current GHC implementation, the call stack is only available 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 () -- | Like trace but returning unit in an arbitrary -- Applicative context. Allows for convenient use in do-notation. -- -- Note that the application of traceM is not an action in the -- Applicative context, as traceIO is in the IO -- type. While the fresh bindings in the following example will force the -- traceM expressions to be reduced every time the -- do-block is executed, traceM "not crashed" would -- only be reduced once, and the message would only be printed once. If -- your monad is in MonadIO, liftIO . traceIO may be a -- better option. -- --
--   ... = do
--     x <- ...
--     traceM $ "x: " ++ show x
--     y <- ...
--     traceM $ "y: " ++ show y
--   
traceM :: (Applicative f) => String -> f () -- | Like traceM, but uses show on the argument to convert it -- to a String. -- --
--   ... = do
--     x <- ...
--     traceShowM $ x
--     y <- ...
--     traceShowM $ x + y
--   
traceShowM :: (Show a, Applicative f) => a -> f () -- | Deprecated: Use 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 () -- | The traceMarker function emits a marker to the eventlog, if -- eventlog profiling is available and enabled at runtime. The -- String is the name of the marker. The name is just used in -- the profiling tools to help you keep clear which marker is which. -- -- This function is suitable for use in pure code. In an IO context use -- traceMarkerIO 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 traceMarker. traceMarker :: String -> a -> a -- | The traceMarkerIO function emits a marker to the eventlog, if -- eventlog profiling is available and enabled at runtime. -- -- Compared to traceMarker, traceMarkerIO sequences the -- event with respect to other IO actions. traceMarkerIO :: String -> IO () -- | 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 (-XOverloadedStrings 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. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
--   lines "" == []
--   lines "\n" == [""]
--   lines "one" == ["one"]
--   lines "one\n" == ["one"]
--   lines "one\n\n" == ["one",""]
--   lines "one\ntwo" == ["one","two"]
--   lines "one\ntwo\n" == ["one","two"]
--   
-- -- Thus lines s contains at least as many elements as -- newlines in s. 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 Data.String.IsString a => Data.String.IsString (Data.Functor.Const.Const a b) instance Data.String.IsString a => Data.String.IsString (Data.Functor.Identity.Identity a) instance a ~ GHC.Types.Char => Data.String.IsString [a] -- | A general library for representation and manipulation of versions. -- -- Versioning schemes are many and varied, so the version representation -- provided by this library is intended to be a compromise between -- complete generality, where almost no common functionality could -- reasonably be provided, and fixing a particular versioning scheme, -- which would probably be too restrictive. -- -- So the approach taken here is to provide a representation which -- subsumes many of the versioning schemes commonly in use, and we -- provide implementations of Eq, Ord and conversion -- to/from String which will be appropriate for some applications, -- but not all. module Data.Version -- | A Version represents the version of a software entity. -- -- An instance of Eq is provided, which implements exact equality -- modulo reordering of the tags in the versionTags field. -- -- An instance of Ord is also provided, which gives lexicographic -- ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 -- > 1.2.2, etc.). This is expected to be sufficient for many uses, -- but note that you may need to use a more specific ordering for your -- versioning scheme. For example, some versioning schemes may include -- pre-releases which have tags "pre1", "pre2", and so -- on, and these would need to be taken into account when determining -- ordering. In some cases, date ordering may be more appropriate, so the -- application would have to look for date tags in the -- versionTags field and compare those. The bottom line is, don't -- always assume that compare and other Ord operations are -- the right thing for every Version. -- -- Similarly, concrete representations of versions may differ. One -- possible concrete representation is provided (see showVersion -- and parseVersion), but depending on the application a different -- concrete representation may be more appropriate. data Version Version :: [Int] -> [String] -> Version -- | The numeric branch for this version. This reflects the fact that most -- software versions are tree-structured; there is a main trunk which is -- tagged with versions at various points (1,2,3...), and the first -- branch off the trunk after version 3 is 3.1, the second branch off the -- trunk after version 3 is 3.2, and so on. The tree can be branched -- arbitrarily, just by adding more digits. -- -- We represent the branch as a list of Int, so version 3.2.1 -- becomes [3,2,1]. Lexicographic ordering (i.e. the default instance of -- Ord for [Int]) gives the natural ordering of branches. [versionBranch] :: Version -> [Int] -- | A version can be tagged with an arbitrary list of strings. The -- interpretation of the list of tags is entirely dependent on the entity -- that this version applies to. -- | Deprecated: See GHC ticket #2496 [versionTags] :: Version -> [String] -- | Provides one possible concrete representation for Version. For -- a version with versionBranch = [1,2,3] and -- versionTags = ["tag1","tag2"], the output will be -- 1.2.3-tag1-tag2. showVersion :: Version -> String -- | A parser for versions in the format produced by showVersion. parseVersion :: ReadP Version -- | Construct tag-less Version makeVersion :: [Int] -> Version instance GHC.Generics.Generic Data.Version.Version instance GHC.Show.Show Data.Version.Version instance GHC.Read.Read Data.Version.Version instance GHC.Classes.Eq Data.Version.Version instance GHC.Classes.Ord Data.Version.Version -- | The Functor, Monad and MonadPlus classes, with -- some useful operations on monads. module Control.Monad -- | 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 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. -- -- Instances of Monad should satisfy the following laws: -- -- -- -- Furthermore, the Monad and Applicative operations should -- relate as follows: -- -- -- -- The above laws imply: -- -- -- -- and that pure and (<*>) satisfy the applicative -- functor laws. -- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Applicative m => Monad m -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. (>>=) :: forall a b. Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. (>>) :: forall a b. Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a -- | Fail with a message. This operation is not part of the mathematical -- definition of a monad, but is invoked on pattern-match failure in a -- do expression. -- -- As part of the MonadFail proposal (MFP), this function is moved to its -- own class MonadFail (see Control.Monad.Fail for more -- details). The definition here will be removed in a future release. fail :: Monad m => String -> m a -- | Monads that also support choice and failure. class (Alternative m, Monad m) => MonadPlus m -- | the identity of mplus. It should also satisfy the equations -- --
--   mzero >>= f  =  mzero
--   v >> mzero   =  mzero
--   
mzero :: MonadPlus m => m a -- | an associative operation mplus :: MonadPlus m => m a -> m a -> m a -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results. For a version -- that ignores the results see mapM_. mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and ignore the results. For a version that -- doesn't ignore the results see mapM. -- -- As of base 4.8.0.0, mapM_ is just traverse_, specialized -- to Monad. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () -- | forM is mapM with its arguments flipped. For a version -- that ignores the results see forM_. forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) -- | forM_ is mapM_ with its arguments flipped. For a version -- that doesn't ignore the results see forM. -- -- As of base 4.8.0.0, forM_ is just for_, specialized to -- Monad. forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m () -- | Evaluate each monadic action in the structure from left to right, and -- collect the results. For a version that ignores the results see -- sequence_. sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) -- | Evaluate each monadic action in the structure from left to right, and -- ignore the results. For a version that doesn't ignore the results see -- sequence. -- -- As of base 4.8.0.0, sequence_ is just sequenceA_, -- specialized to Monad. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | Left-to-right Kleisli composition of monads. (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) infixr 1 >=> -- | Right-to-left Kleisli composition of monads. -- (>=>), with the arguments flipped. -- -- Note how this operator resembles function composition -- (.): -- --
--   (.)   ::            (b ->   c) -> (a ->   b) -> a ->   c
--   (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
--   
(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c) infixr 1 <=< -- | forever act repeats the action infinitely. forever :: (Applicative f) => f a -> f b -- | void value discards or ignores the result of -- evaluation, such as the return value of an IO action. -- --

Examples

-- -- Replace the contents of a Maybe Int with -- unit: -- --
--   >>> void Nothing
--   Nothing
--   
--   >>> void (Just 3)
--   Just ()
--   
-- -- Replace the contents of an Either Int -- Int with unit, resulting in an Either -- Int '()': -- --
--   >>> void (Left 8675309)
--   Left 8675309
--   
--   >>> void (Right 8675309)
--   Right ()
--   
-- -- Replace every element of a list with unit: -- --
--   >>> void [1,2,3]
--   [(),(),()]
--   
-- -- Replace the second element of a pair with unit: -- --
--   >>> void (1,2)
--   (1,())
--   
-- -- Discard the result of an IO action: -- --
--   >>> mapM print [1,2]
--   1
--   2
--   [(),()]
--   
--   >>> void $ mapM print [1,2]
--   1
--   2
--   
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 -- | The sum of a collection of actions, generalizing concat. As of -- base 4.8.0.0, msum is just asum, specialized to -- MonadPlus. msum :: (Foldable t, MonadPlus m) => t (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 :: (Applicative 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 :: (Applicative m) => (a -> m (b, c)) -> [a] -> m ([b], [c]) -- | The zipWithM function generalizes zipWith to arbitrary -- applicative functors. zipWithM :: (Applicative m) => (a -> b -> m c) -> [a] -> [b] -> m [c] -- | zipWithM_ is the extension of zipWithM which ignores the -- final result. zipWithM_ :: (Applicative 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. -- -- Note: foldM is the same as foldlM foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b -- | Like foldM, but discards the result. foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () -- | replicateM n act performs the action n times, -- gathering the results. replicateM :: (Applicative m) => Int -> m a -> m [a] -- | Like replicateM, but discards the result. replicateM_ :: (Applicative m) => Int -> m a -> m () -- | guard b is pure () if b is -- True, and empty if b is False. guard :: (Alternative f) => Bool -> f () -- | Conditional execution of Applicative expressions. For example, -- --
--   when debug (putStrLn "Debugging")
--   
-- -- will output the string Debugging if the Boolean value -- debug is True, and otherwise do nothing. when :: (Applicative f) => Bool -> f () -> f () -- | The reverse of when. unless :: (Applicative f) => Bool -> f () -> f () -- | 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 -- | Strict version of <$>. (<$!>) :: Monad m => (a -> b) -> m a -> m b infixl 4 <$!> -- | The Prelude: a standard module. The Prelude is imported by default -- into all Haskell modules unless either there is an explicit import -- statement for it, or the NoImplicitPrelude extension is enabled. module Prelude data Bool :: * False :: Bool True :: Bool -- | Boolean "and" (&&) :: Bool -> Bool -> Bool infixr 3 && -- | Boolean "or" (||) :: Bool -> Bool -> Bool infixr 2 || -- | 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. -- --

Examples

-- -- Basic usage: -- --
--   >>> maybe False odd (Just 3)
--   True
--   
-- --
--   >>> maybe False odd Nothing
--   False
--   
-- -- Read an integer from a string using readMaybe. If we succeed, -- return twice the integer; that is, apply (*2) to it. If -- instead we fail to parse an integer, return 0 by default: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> maybe 0 (*2) (readMaybe "5")
--   10
--   
--   >>> maybe 0 (*2) (readMaybe "")
--   0
--   
-- -- Apply show to a Maybe Int. If we have Just -- n, we want to show the underlying Int n. But if -- we have Nothing, we return the empty string instead of (for -- example) "Nothing": -- --
--   >>> maybe "" show (Just 5)
--   "5"
--   
--   >>> maybe "" show Nothing
--   ""
--   
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"). -- --

Examples

-- -- The type Either String Int is the type -- of values which can be either a String or an Int. The -- Left constructor can be used only on Strings, and the -- Right constructor can be used only on Ints: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> s
--   Left "foo"
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> n
--   Right 3
--   
--   >>> :type s
--   s :: Either String Int
--   
--   >>> :type n
--   n :: Either String Int
--   
-- -- The fmap from our Functor instance will ignore -- Left values, but will apply the supplied function to values -- contained in a Right: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> fmap (*2) s
--   Left "foo"
--   
--   >>> fmap (*2) n
--   Right 6
--   
-- -- The Monad instance for Either allows us to chain -- together multiple actions which may fail, and fail overall if any of -- the individual steps failed. First we'll write a function that can -- either parse an Int from a Char, or fail. -- --
--   >>> import Data.Char ( digitToInt, isDigit )
--   
--   >>> :{
--       let parseEither :: Char -> Either String Int
--           parseEither c
--             | isDigit c = Right (digitToInt c)
--             | otherwise = Left "parse error"
--   
--   >>> :}
--   
-- -- The following should work, since both '1' and '2' -- can be parsed as Ints. -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither '1'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Right 3
--   
-- -- But the following should fail overall, since the first operation where -- we attempt to parse 'm' as an Int will fail: -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither 'm'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Left "parse error"
--   
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. -- --

Examples

-- -- We create two values of type Either String -- Int, one using the Left constructor and another -- using the Right constructor. Then we apply "either" the -- length function (if we have a String) or the -- "times-two" function (if we have an Int): -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> either length (*2) s
--   3
--   
--   >>> either length (*2) n
--   6
--   
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 -- | the successor of a value. For numeric types, succ adds 1. succ :: Enum a => a -> a -- | the predecessor of a value. For numeric types, pred subtracts -- 1. pred :: Enum a => a -> a -- | Convert from an Int. toEnum :: Enum a => Int -> a -- | Convert to an Int. It is implementation-dependent what -- fromEnum returns when applied to a value that is too large to -- fit in an Int. fromEnum :: Enum a => a -> Int -- | Used in Haskell's translation of [n..]. enumFrom :: Enum a => a -> [a] -- | Used in Haskell's translation of [n,n'..]. enumFromThen :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n..m]. enumFromTo :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n,n'..m]. 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 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 :: * -- | Invariant: Jn# and Jp# are used iff value doesn't fit in -- S# -- -- Useful properties resulting from the invariants: -- -- 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 -- | A Word is an unsigned integral type, with the same size as -- Int. data Word :: * -- | Basic numeric class. class Num a (+, -, *) :: Num a => a -> a -> a (+, -, *) :: Num a => a -> a -> a (+, -, *) :: Num a => a -> a -> a -- | Unary negation. negate :: Num a => a -> a -- | Absolute value. abs :: Num a => a -> a -- | Sign of a number. The functions abs and signum should -- satisfy the law: -- --
--   abs x * signum x == x
--   
-- -- For real numbers, the signum is either -1 (negative), -- 0 (zero) or 1 (positive). signum :: Num a => a -> a -- | Conversion from an Integer. An integer literal represents the -- application of the function fromInteger to the appropriate -- value of type Integer, so such literals have type -- (Num a) => a. fromInteger :: Num a => Integer -> a class (Num a, Ord a) => Real a -- | the rational equivalent of its real argument with full precision toRational :: Real a => a -> Rational -- | Integral numbers, supporting integer division. class (Real a, Enum a) => Integral a -- | integer division truncated toward zero quot :: Integral a => a -> a -> a -- | integer remainder, satisfying -- --
--   (x `quot` y)*y + (x `rem` y) == x
--   
rem :: Integral a => a -> a -> a -- | integer division truncated toward negative infinity div :: Integral a => a -> a -> a -- | integer modulus, satisfying -- --
--   (x `div` y)*y + (x `mod` y) == x
--   
mod :: Integral a => a -> a -> a -- | simultaneous quot and rem quotRem :: Integral a => a -> a -> (a, a) -- | simultaneous div and mod divMod :: Integral a => a -> a -> (a, a) -- | conversion to Integer toInteger :: Integral a => a -> Integer -- | Fractional numbers, supporting real division. class (Num a) => Fractional a -- | fractional division (/) :: Fractional a => a -> a -> a -- | reciprocal fraction recip :: Fractional a => a -> a -- | Conversion from a Rational (that is Ratio -- Integer). A floating literal stands for an application of -- fromRational to a value of type Rational, so such -- literals have type (Fractional a) => a. fromRational :: Fractional a => Rational -> a -- | Trigonometric and hyperbolic functions and related functions. class (Fractional a) => Floating a pi :: Floating a => a exp, log, sqrt :: Floating a => a -> a exp, log, sqrt :: Floating a => a -> a exp, log, sqrt :: Floating a => a -> a (**, logBase) :: Floating a => a -> a -> a (**, logBase) :: Floating a => a -> a -> a sin, cos, tan :: Floating a => a -> a sin, cos, tan :: Floating a => a -> a sin, cos, tan :: Floating a => a -> a asin, acos, atan :: Floating a => a -> a asin, acos, atan :: Floating a => a -> a asin, acos, atan :: Floating a => a -> a sinh, cosh, tanh :: Floating a => a -> a sinh, cosh, tanh :: Floating a => a -> a sinh, cosh, tanh :: Floating a => a -> a asinh, acosh, atanh :: Floating a => a -> a asinh, acosh, atanh :: Floating a => a -> a asinh, acosh, atanh :: Floating a => a -> a -- | Extracting components of fractions. class (Real a, Fractional a) => RealFrac a -- | The function properFraction takes a real fractional number -- x and returns a pair (n,f) such that x = -- n+f, and: -- -- -- -- The default definitions of the ceiling, floor, -- truncate and round functions are in terms of -- properFraction. properFraction :: (RealFrac a, (Integral b)) => a -> (b, a) -- | truncate x returns the integer nearest x -- between zero and x truncate :: (RealFrac a, (Integral b)) => a -> b -- | round x returns the nearest integer to x; the -- even integer if x is equidistant between two integers round :: (RealFrac a, (Integral b)) => a -> b -- | ceiling x returns the least integer not less than -- x ceiling :: (RealFrac a, (Integral b)) => a -> b -- | floor x returns the greatest integer not greater than -- x floor :: (RealFrac a, (Integral b)) => a -> b -- | Efficient, machine-independent access to the components of a -- floating-point number. class (RealFrac a, Floating a) => RealFloat a -- | a constant function, returning the radix of the representation (often -- 2) floatRadix :: RealFloat a => a -> Integer -- | a constant function, returning the number of digits of -- floatRadix in the significand floatDigits :: RealFloat a => a -> Int -- | a constant function, returning the lowest and highest values the -- exponent may assume floatRange :: RealFloat a => a -> (Int, Int) -- | The function decodeFloat applied to a real floating-point -- number returns the significand expressed as an Integer and an -- appropriately scaled exponent (an Int). If -- decodeFloat x yields (m,n), then x -- is equal in value to m*b^^n, where b is the -- floating-point radix, and furthermore, either m and -- n are both zero or else b^(d-1) <= abs m < -- b^d, where d is the value of floatDigits -- x. In particular, decodeFloat 0 = (0,0). If the -- type contains a negative zero, also decodeFloat (-0.0) = -- (0,0). The result of decodeFloat x is -- unspecified if either of isNaN x or -- isInfinite x is True. decodeFloat :: RealFloat a => a -> (Integer, Int) -- | encodeFloat performs the inverse of decodeFloat in the -- sense that for finite x with the exception of -0.0, -- uncurry encodeFloat (decodeFloat x) = -- x. encodeFloat m n is one of the two closest -- representable floating-point numbers to m*b^^n (or -- ±Infinity if overflow occurs); usually the closer, but if -- m contains too many bits, the result may be rounded in the -- wrong direction. encodeFloat :: RealFloat a => Integer -> Int -> a -- | exponent corresponds to the second component of -- decodeFloat. exponent 0 = 0 and for finite -- nonzero x, exponent x = snd (decodeFloat x) -- + floatDigits x. If x is a finite floating-point -- number, it is equal in value to significand x * b ^^ -- exponent x, where b is the floating-point radix. -- The behaviour is unspecified on infinite or NaN values. exponent :: RealFloat a => a -> Int -- | The first component of decodeFloat, scaled to lie in the open -- interval (-1,1), either 0.0 or of absolute -- value >= 1/b, where b is the floating-point -- radix. The behaviour is unspecified on infinite or NaN -- values. significand :: RealFloat a => a -> a -- | multiplies a floating-point number by an integer power of the radix scaleFloat :: RealFloat a => Int -> a -> a -- | True if the argument is an IEEE "not-a-number" (NaN) value isNaN :: RealFloat a => a -> Bool -- | True if the argument is an IEEE infinity or negative infinity isInfinite :: RealFloat a => a -> Bool -- | True if the argument is too small to be represented in -- normalized format isDenormalized :: RealFloat a => a -> Bool -- | True if the argument is an IEEE negative zero isNegativeZero :: RealFloat a => a -> Bool -- | True if the argument is an IEEE floating point number isIEEE :: RealFloat a => a -> Bool -- | a version of arctangent taking two real floating-point arguments. For -- real floating x and y, atan2 y x -- computes the angle (from the positive x-axis) of the vector from the -- origin to the point (x,y). atan2 y x returns -- a value in the range [-pi, pi]. It follows the -- Common Lisp semantics for the origin when signed zeroes are supported. -- atan2 y 1, with y in a type that is -- RealFloat, should return the same value as atan -- y. A default definition of atan2 is provided, but -- implementors can provide a more accurate implementation. 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 infixr 8 ^ -- | raise a number to an integral power (^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 ^^ -- | 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 class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following laws: -- -- -- -- The method names refer to the monoid of lists under concatenation, but -- there are many other instances. -- -- Some types can be viewed as a monoid in more than one way, e.g. both -- addition and multiplication on numbers. In such cases we often define -- newtypes and make those instances of Monoid, e.g. -- Sum and Product. class Monoid a -- | Identity of mappend mempty :: Monoid a => a -- | An associative operation mappend :: Monoid a => a -> a -> a -- | Fold a list using the monoid. For most types, the default definition -- for mconcat will be used, but the function is included in the -- class definition so that an optimized version can be provided for -- specific types. mconcat :: Monoid a => [a] -> 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 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 -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
--    ($)  ::              (a -> b) ->   a ->   b
--   (<$>) :: Functor f => (a -> b) -> f a -> f b
--   
-- -- Whereas $ is function application, <$> is -- function application lifted over a Functor. -- --

Examples

-- -- Convert from a Maybe Int to a -- Maybe String using show: -- --
--   >>> show <$> Nothing
--   Nothing
--   
--   >>> show <$> Just 3
--   Just "3"
--   
-- -- Convert from an Either Int Int to -- an Either Int String using -- show: -- --
--   >>> show <$> Left 17
--   Left 17
--   
--   >>> show <$> Right 17
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> (*2) <$> [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> even <$> (2,2)
--   (2,True)
--   
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 <$> -- | A functor with application, providing operations to -- -- -- -- A minimal complete definition must include implementations of -- pure and of either <*> or liftA2. If it -- defines both, then they must behave the same as their default -- definitions: -- -- (<*>) = liftA2 id -- liftA2 f x y = f <$> x <*> -- y -- -- Further, any definition must satisfy the following: -- -- -- -- The other methods have the following default definitions, which may be -- overridden with equivalent specialized implementations: -- -- -- -- As a consequence of these laws, the Functor instance for -- f will satisfy -- -- -- -- It may be useful to note that supposing -- --
--   forall x y. p (q x y) = f x . g y
--   
-- -- it follows from the above that -- --
--   liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v
--   
-- -- If f is also a Monad, it should satisfy -- -- -- -- (which implies that pure and <*> satisfy the -- applicative functor laws). class Functor f => Applicative f -- | Lift a value. pure :: Applicative f => a -> f a -- | Sequential application. -- -- A few functors support an implementation of <*> that is -- more efficient than the default one. (<*>) :: Applicative f => f (a -> b) -> f a -> f b -- | Sequence actions, discarding the value of the first argument. (*>) :: Applicative f => f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. (<*) :: Applicative f => f a -> f b -> f a -- | 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. -- -- Instances of Monad should satisfy the following laws: -- -- -- -- Furthermore, the Monad and Applicative operations should -- relate as follows: -- -- -- -- The above laws imply: -- -- -- -- and that pure and (<*>) satisfy the applicative -- functor laws. -- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Applicative m => Monad m -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. (>>=) :: forall a b. Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. (>>) :: forall a b. Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a -- | Fail with a message. This operation is not part of the mathematical -- definition of a monad, but is invoked on pattern-match failure in a -- do expression. -- -- As part of the MonadFail proposal (MFP), this function is moved to its -- own class MonadFail (see Control.Monad.Fail for more -- details). The definition here will be removed in a future release. fail :: Monad m => String -> m a -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and ignore the results. For a version that -- doesn't ignore the results see mapM. -- -- As of base 4.8.0.0, mapM_ is just traverse_, specialized -- to Monad. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () -- | Evaluate each monadic action in the structure from left to right, and -- ignore the results. For a version that doesn't ignore the results see -- sequence. -- -- As of base 4.8.0.0, sequence_ is just sequenceA_, -- specialized to Monad. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | Data structures that can be folded. -- -- 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
--   
-- -- Foldable instances are expected to satisfy the following -- laws: -- --
--   foldr f z t = appEndo (foldMap (Endo . f) t ) z
--   
-- --
--   foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
--   
-- --
--   fold = foldMap id
--   
-- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
--   sum = getSum . foldMap Sum
--   
-- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
--   foldMap f = fold . fmap f
--   
-- -- which implies that -- --
--   foldMap f . fmap g = foldMap (f . g)
--   
class Foldable t -- | Map each element of the structure to a monoid, and combine the -- results. foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | Right-associative fold of a structure. -- -- In the case of lists, foldr, when 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)...)
--   
-- -- Note that, since the head of the resulting expression is produced by -- an application of the operator to the first element of the list, -- foldr can produce a terminating expression from an infinite -- list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldr f z = foldr f z . toList
--   
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Left-associative fold of a structure. -- -- In the case of lists, foldl, when 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
--   
-- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldl' -- will diverge if given an infinite list. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is -- that latter does not force the "inner" results (e.g. z f -- x1 in the above example) before applying them to the operator -- (e.g. to (f x2)). This results in a thunk chain -- O(n) elements long, which then must be evaluated from the -- outside-in. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldl f z = foldl f z . toList
--   
foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | A variant of foldr that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldr1 f = foldr1 f . toList
--   
foldr1 :: Foldable t => (a -> a -> a) -> t a -> a -- | A variant of foldl that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldl1 f = foldl1 f . toList
--   
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. length :: Foldable t => t a -> Int -- | Does the element occur in the structure? elem :: (Foldable t, Eq a) => a -> t a -> Bool -- | The largest element of a non-empty structure. maximum :: forall a. (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure. minimum :: forall a. (Foldable t, Ord a) => t a -> a -- | 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 -- | Functors representing data structures that can be traversed from left -- to right. -- -- A definition of traverse must satisfy the following laws: -- -- -- -- A definition of sequenceA must satisfy the following laws: -- -- -- -- where an applicative transformation is a function -- --
--   t :: (Applicative f, Applicative g) => f a -> g a
--   
-- -- preserving the Applicative operations, i.e. -- -- -- -- and the identity functor Identity and composition of functors -- Compose are defined as -- --
--   newtype Identity a = Identity a
--   
--   instance Functor Identity where
--     fmap f (Identity x) = Identity (f x)
--   
--   instance Applicative Identity where
--     pure x = Identity x
--     Identity f <*> Identity x = Identity (f x)
--   
--   newtype Compose f g a = Compose (f (g a))
--   
--   instance (Functor f, Functor g) => Functor (Compose f g) where
--     fmap f (Compose x) = Compose (fmap (fmap f) x)
--   
--   instance (Applicative f, Applicative g) => Applicative (Compose f g) where
--     pure x = Compose (pure (pure x))
--     Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
--   
-- -- (The naturality law is implied by parametricity.) -- -- Instances are similar to Functor, e.g. given a data type -- --
--   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: -- -- class (Functor t, Foldable t) => Traversable t -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and collect the results. For a version that -- ignores the results see traverse_. traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) -- | Evaluate each action in the structure from left to right, and and -- collect the results. For a version that ignores the results see -- sequenceA_. sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a) -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results. For a version -- that ignores the results see mapM_. mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) -- | Evaluate each monadic action in the structure from left to right, and -- collect the results. For a version that ignores the results see -- sequence_. sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) -- | Identity function. id :: a -> a -- | const x is a unary function which evaluates to x for -- all inputs. -- -- For instance, -- --
--   >>> map (const 42) [0..3]
--   [42,42,42,42]
--   
const :: a -> b -> a -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | 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 infixr 0 $ -- | 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 :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => [Char] -> a -- | A variant of error that does not produce a stack trace. errorWithoutStackTrace :: forall (r :: RuntimeRep). forall (a :: TYPE r). [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 :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => a -- | The value of seq a b is bottom if a is bottom, and -- otherwise equal to b. seq is usually introduced to -- improve performance by avoiding unneeded laziness. -- -- A note on evaluation order: the expression seq a b does -- not guarantee that a will be evaluated before -- b. The only guarantee given by seq is that the both -- a and b will be evaluated before seq -- returns a value. In particular, this means that b may be -- evaluated before a. If you need to guarantee a specific order -- of evaluation, you must use the function pseq from the -- "parallel" package. seq :: () => a -> b -> b -- | Strict (call-by-value) application operator. It takes a function and -- an argument, evaluates the argument to weak head normal form (WHNF), -- then calls the function with that value. ($!) :: (a -> b) -> a -> b infixr 0 $! -- | 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] infixr 5 ++ -- | 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 the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. length :: Foldable t => t 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 infixl 9 !! -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. reverse :: [a] -> [a] -- | 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 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] -- | 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 :: (b -> a -> b) -> b -> [a] -> [b] -- | 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]) -- | notElem is the negation of elem. notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `notElem` -- | 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 is right-lazy: -- --
--   zip [] _|_ = []
--   
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 is right-lazy: -- --
--   zipWith f [] _|_ = []
--   
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. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
--   lines "" == []
--   lines "\n" == [""]
--   lines "one" == ["one"]
--   lines "one\n" == ["one"]
--   lines "one\n\n" == ["one",""]
--   lines "one\ntwo" == ["one","two"]
--   lines "one\ntwo\n" == ["one","two"]
--   
-- -- Thus lines s contains at least as many elements as -- newlines in s. 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. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- For example, given the declarations -- --
--   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, -- -- class Show a -- | Convert a value to a readable String. -- -- showsPrec should satisfy the law -- --
--   showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)
--   
-- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. showsPrec :: Show a => Int -> a -> ShowS -- | A specialised variant of showsPrec, using precedence context -- zero, and returning an ordinary String. show :: Show a => a -> String -- | The method showList is provided to allow the programmer to give -- a specialised way of showing lists of values. For example, this is -- used by the predefined Show instance of the Char type, -- where values of type String should be shown in double quotes, -- rather than between square brackets. showList :: Show a => [a] -> ShowS -- | equivalent to showsPrec with a precedence of 0. shows :: (Show a) => a -> ShowS -- | utility function converting a Char to a show function that -- simply prepends the character unchanged. showChar :: Char -> ShowS -- | utility function converting a String to a show function that -- simply prepends the string unchanged. showString :: String -> ShowS -- | utility function that surrounds the inner show function with -- parentheses when the Bool parameter is True. showParen :: Bool -> ShowS -> ShowS -- | 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)] -- | Parsing of Strings, producing values. -- -- Derived instances of Read make the following assumptions, which -- derived instances of Show obey: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Read in Haskell 2010 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
--   
-- -- Why do both readsPrec and readPrec exist, and why does -- GHC opt to implement readPrec in derived Read instances -- instead of readsPrec? The reason is that readsPrec is -- based on the ReadS type, and although ReadS is mentioned -- in the Haskell 2010 Report, it is not a very efficient parser data -- structure. -- -- readPrec, on the other hand, is based on a much more efficient -- ReadPrec datatype (a.k.a "new-style parsers"), but its -- definition relies on the use of the RankNTypes language -- extension. Therefore, readPrec (and its cousin, -- readListPrec) are marked as GHC-only. Nevertheless, it is -- recommended to use readPrec instead of readsPrec -- whenever possible for the efficiency improvements it brings. -- -- As mentioned above, derived Read instances in GHC will -- implement readPrec instead of readsPrec. The default -- implementations of readsPrec (and its cousin, readList) -- will simply use readPrec under the hood. If you are writing a -- Read instance by hand, it is recommended to write it like so: -- --
--   instance Read T where
--     readPrec     = ...
--     readListPrec = readListPrecDefault
--   
class Read a -- | attempts to parse a value from the front of the string, returning a -- list of (parsed value, remaining string) pairs. If there is no -- successful parse, the returned list is empty. -- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. readsPrec :: Read a => Int -> ReadS a -- | The method readList is provided to allow the programmer to give -- a specialised way of parsing lists of values. For example, this is -- used by the predefined Read instance of the Char type, -- where values of type String should be are expected to use -- double quotes, rather than square brackets. 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: -- -- lex :: ReadS String -- | A value of type IO a is a computation which, when -- performed, does some I/O before returning a value of type a. -- -- There is really only one way to "perform" an I/O action: bind it to -- Main.main in your program. When your program is run, the I/O -- will be performed. It isn't possible to perform I/O from an arbitrary -- function, unless that function is itself in the IO monad and -- called at some point, directly or indirectly, from Main.main. -- -- IO is a monad, so IO actions can be combined using -- either the do-notation or the >> and >>= -- operations from the Monad class. data IO a :: * -> * -- | Write a character to the standard output device (same as -- hPutChar stdout). putChar :: Char -> IO () -- | Write a string to the standard output device (same as hPutStr -- stdout). putStr :: String -> IO () -- | The same as putStr, but adds a newline character. putStrLn :: String -> IO () -- | The print function outputs a value of any printable type to the -- standard output device. Printable types are those that are instances -- of class Show; print converts values to strings for -- output using the show operation and adds a newline. -- -- For example, a program to print the first 20 integers and their powers -- of 2 could be written as: -- --
--   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 2010 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 Exception. -- -- In Haskell 2010, 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 representations of the types TyCon and TypeRep, and -- the function mkTyCon which is used by derived instances of -- Typeable to construct TyCons. -- -- Be warned, these functions can be used to construct ill-kinded type -- representations. module Type.Reflection.Unsafe -- | A concrete representation of a (monomorphic) type. TypeRep -- supports reasonably efficient equality. data TypeRep (a :: k) -- | Construct a representation for a type application. -- -- Note that this is known-key to the compiler, which uses it in desugar -- Typeable evidence. mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep (a :: k1 -> k2) -> TypeRep (b :: k1) -> TypeRep (a b) -- | Exquisitely unsafe. mkTyCon :: String -> String -> String -> Int -> KindRep -> TyCon -- | Observe the Fingerprint of a type representation typeRepFingerprint :: TypeRep a -> Fingerprint someTypeRepFingerprint :: SomeTypeRep -> Fingerprint -- | The representation produced by GHC for conjuring up the kind of a -- TypeRep. data KindRep :: * KindRepTyConApp :: TyCon -> [KindRep] -> KindRep KindRepVar :: !KindBndr -> KindRep KindRepApp :: KindRep -> KindRep -> KindRep KindRepFun :: KindRep -> KindRep -> KindRep KindRepTYPE :: !RuntimeRep -> KindRep KindRepTypeLitS :: TypeLitSort -> Addr# -> KindRep KindRepTypeLitD :: TypeLitSort -> [Char] -> KindRep data TypeLitSort :: * TypeLitSymbol :: TypeLitSort TypeLitNat :: TypeLitSort data TyCon :: * -- | Construct a representation for a type constructor applied at a -- monomorphic kind. -- -- Note that this is unsafe as it allows you to construct ill-kinded -- types. mkTrCon :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a tyConKindRep :: TyCon -> KindRep tyConKindArgs :: TyCon -> Int tyConFingerprint :: TyCon -> Fingerprint -- | Optional instance of Show for functions: -- --
--   instance Show (a -> b) where
--      showsPrec _ _ = showString \"\<function\>\"
--   
module Text.Show.Functions instance GHC.Show.Show (a -> b) -- | A C printf(3)-like formatter. This version has been extended -- by Bart Massey as per the recommendations of John Meacham and Simon -- Marlow -- <http://comments.gmane.org/gmane.comp.lang.haskell.libraries/4726> -- to support extensible formatting for new datatypes. It has also been -- extended to support almost all C printf(3) syntax. module Text.Printf -- | Format a variable number of arguments with the C-style formatting -- string. The return value is either String or (IO -- a) (which should be (IO '()'), but Haskell's type -- system makes this hard). -- -- 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 format specification is -- introduced by the % character; this character can be -- self-escaped into the format string using %%. A format -- specification ends with a /format character/ that provides the primary -- information about how to format the value. The rest of the conversion -- specification is optional. In order, one may have flag characters, a -- width specifier, a precision specifier, and type-specific modifier -- characters. -- -- Unlike C printf(3), the formatting of this printf is -- driven by the argument type; formatting is type specific. The types -- formatted by printf "out of the box" are: -- -- -- -- printf is also extensible to support other types: see below. -- -- A conversion specification begins with the character %, -- followed by zero or more of the following flags: -- --
--   -      left adjust (default is right adjust)
--   +      always use a sign (+ or -) for signed conversions
--   space  leading space for positive numbers in signed conversions
--   0      pad with zeros rather than spaces
--   #      use an \"alternate form\": see below
--   
-- -- When both flags are given, - overrides 0 and -- + overrides space. A negative width specifier in a * -- conversion is treated as positive but implies the left adjust flag. -- -- The "alternate form" for unsigned radix conversions is as in C -- printf(3): -- --
--   %o           prefix with a leading 0 if needed
--   %x           prefix with a leading 0x if nonzero
--   %X           prefix with a leading 0X if nonzero
--   %b           prefix with a leading 0b if nonzero
--   %[eEfFgG]    ensure that the number contains a decimal point
--   
-- -- Any flags are followed optionally by a field width: -- --
--   num    field width
--   *      as num, but taken from argument list
--   
-- -- The field width is a minimum, not a maximum: it will be expanded as -- needed to avoid mutilating a value. -- -- Any field width is followed optionally by a precision: -- --
--   .num   precision
--   .      same as .0
--   .*     as num, but taken from argument list
--   
-- -- Negative precision is taken as 0. The meaning of the precision depends -- on the conversion type. -- --
--   Integral    minimum number of digits to show
--   RealFloat   number of digits after the decimal point
--   String      maximum number of characters
--   
-- -- The precision for Integral types is accomplished by zero-padding. If -- both precision and zero-pad are given for an Integral field, the -- zero-pad is ignored. -- -- Any precision is followed optionally for Integral types by a width -- modifier; the only use of this modifier being to set the implicit size -- of the operand for conversion of a negative operand to unsigned: -- --
--   hh     Int8
--   h      Int16
--   l      Int32
--   ll     Int64
--   L      Int64
--   
-- -- The specification ends with a format character: -- --
--   c      character               Integral
--   d      decimal                 Integral
--   o      octal                   Integral
--   x      hexadecimal             Integral
--   X      hexadecimal             Integral
--   b      binary                  Integral
--   u      unsigned decimal        Integral
--   f      floating point          RealFloat
--   F      floating point          RealFloat
--   g      general format float    RealFloat
--   G      general format float    RealFloat
--   e      exponent format float   RealFloat
--   E      exponent format float   RealFloat
--   s      string                  String
--   v      default format          any type
--   
-- -- The "%v" specifier is provided for all built-in types, and should be -- provided for user-defined type formatters as well. It picks a "best" -- representation for the given type. For the built-in types the "%v" -- specifier is converted as follows: -- --
--   c      Char
--   u      other unsigned Integral
--   d      other signed Integral
--   g      RealFloat
--   s      String
--   
-- -- Mismatch between the argument types and the format string, as well as -- any other syntactic or semantic errors in the format string, will -- cause an exception to be thrown at runtime. -- -- Note that the formatting for RealFloat types is currently a bit -- different from that of C printf(3), conforming instead to -- showEFloat, showFFloat and showGFloat (and their -- alternate versions showFFloatAlt and showGFloatAlt). -- This is hard to fix: the fixed versions would format in a -- backward-incompatible way. In any case the Haskell behavior is -- generally more sensible than the C behavior. A brief summary of some -- key differences: -- -- -- --

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 -- | Typeclass of printf-formattable values. The formatArg -- method takes a value and a field format descriptor and either fails -- due to a bad descriptor or produces a ShowS as the result. The -- default parseFormat expects no modifiers: this is the normal -- case. Minimal instance: formatArg. class PrintfArg a formatArg :: PrintfArg a => a -> FieldFormatter parseFormat :: PrintfArg a => a -> ModifierParser -- | This is the type of a field formatter reified over its argument. type FieldFormatter = FieldFormat -> ShowS -- | Description of field formatting for formatArg. See UNIX -- printf(3) for a description of how field formatting works. data FieldFormat FieldFormat :: Maybe Int -> Maybe Int -> Maybe FormatAdjustment -> Maybe FormatSign -> Bool -> String -> Char -> FieldFormat -- | Total width of the field. [fmtWidth] :: FieldFormat -> Maybe Int -- | Secondary field width specifier. [fmtPrecision] :: FieldFormat -> Maybe Int -- | Kind of filling or padding to be done. [fmtAdjust] :: FieldFormat -> Maybe FormatAdjustment -- | Whether to insist on a plus sign for positive numbers. [fmtSign] :: FieldFormat -> Maybe FormatSign -- | Indicates an "alternate format". See printf(3) for the details, which -- vary by argument spec. [fmtAlternate] :: FieldFormat -> Bool -- | Characters that appeared immediately to the left of fmtChar in -- the format and were accepted by the type's parseFormat. -- Normally the empty string. [fmtModifiers] :: FieldFormat -> String -- | The format character printf was invoked with. formatArg -- should fail unless this character matches the type. It is normal to -- handle many different format characters for a single type. [fmtChar] :: FieldFormat -> Char -- | Whether to left-adjust or zero-pad a field. These are mutually -- exclusive, with LeftAdjust taking precedence. data FormatAdjustment LeftAdjust :: FormatAdjustment ZeroPad :: FormatAdjustment -- | How to handle the sign of a numeric field. These are mutually -- exclusive, with SignPlus taking precedence. data FormatSign SignPlus :: FormatSign SignSpace :: FormatSign -- | Substitute a 'v' format character with the given default format -- character in the FieldFormat. A convenience for -- user-implemented types, which should support "%v". vFmt :: Char -> FieldFormat -> FieldFormat -- | Type of a function that will parse modifier characters from the format -- string. type ModifierParser = String -> FormatParse -- | The "format parser" walks over argument-type-specific modifier -- characters to find the primary format character. This is the type of -- its result. data FormatParse FormatParse :: String -> Char -> String -> FormatParse -- | Any modifiers found. [fpModifiers] :: FormatParse -> String -- | Primary format character. [fpChar] :: FormatParse -> Char -- | Rest of the format string. [fpRest] :: FormatParse -> String -- | Formatter for String values. formatString :: IsChar a => [a] -> FieldFormatter -- | Formatter for Char values. formatChar :: Char -> FieldFormatter -- | Formatter for Int values. formatInt :: (Integral a, Bounded a) => a -> FieldFormatter -- | Formatter for Integer values. formatInteger :: Integer -> FieldFormatter -- | Formatter for RealFloat values. formatRealFloat :: RealFloat a => a -> FieldFormatter -- | Calls perror to indicate an unknown format letter for a given -- type. errorBadFormat :: Char -> a -- | Calls perror to indicate that the format string ended early. errorShortFormat :: a -- | Calls perror to indicate that there is a missing argument in -- the argument list. errorMissingArgument :: a -- | Calls perror to indicate that there is a type error or similar -- in the given argument. errorBadArgument :: a -- | Raises an error with a printf-specific prefix on the message -- string. perror :: String -> a -- | 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 -- | This class, with only the one instance, is used as a workaround for -- the fact that String, as a concrete type, is not allowable as a -- typeclass instance. IsChar is exported for -- backward-compatibility. class IsChar c toChar :: IsChar c => c -> Char fromChar :: IsChar c => Char -> c instance Text.Printf.IsChar c => Text.Printf.PrintfType [c] instance a ~ () => Text.Printf.PrintfType (GHC.Types.IO a) instance (Text.Printf.PrintfArg a, Text.Printf.PrintfType r) => Text.Printf.PrintfType (a -> r) instance a ~ () => Text.Printf.HPrintfType (GHC.Types.IO a) instance (Text.Printf.PrintfArg a, Text.Printf.HPrintfType r) => Text.Printf.HPrintfType (a -> r) instance Text.Printf.PrintfArg GHC.Types.Char instance Text.Printf.IsChar c => Text.Printf.PrintfArg [c] instance Text.Printf.PrintfArg GHC.Types.Int instance Text.Printf.PrintfArg GHC.Int.Int8 instance Text.Printf.PrintfArg GHC.Int.Int16 instance Text.Printf.PrintfArg GHC.Int.Int32 instance Text.Printf.PrintfArg GHC.Int.Int64 instance Text.Printf.PrintfArg GHC.Types.Word instance Text.Printf.PrintfArg GHC.Word.Word8 instance Text.Printf.PrintfArg GHC.Word.Word16 instance Text.Printf.PrintfArg GHC.Word.Word32 instance Text.Printf.PrintfArg GHC.Word.Word64 instance Text.Printf.PrintfArg GHC.Integer.Type.Integer instance Text.Printf.PrintfArg GHC.Natural.Natural instance Text.Printf.PrintfArg GHC.Types.Float instance Text.Printf.PrintfArg GHC.Types.Double instance Text.Printf.IsChar GHC.Types.Char -- | In general terms, a weak pointer is a reference to an object that is -- not followed by the garbage collector - that is, the existence of a -- weak pointer to an object has no effect on the lifetime of that -- object. A weak pointer can be de-referenced to find out whether the -- object it refers to is still alive or not, and if so to return the -- object itself. -- -- Weak pointers are particularly useful for caches and memo tables. To -- build a memo table, you build a data structure mapping from the -- function argument (the key) to its result (the value). When you apply -- the function to a new argument you first check whether the key/value -- pair is already in the memo table. The key point is that the memo -- table itself should not keep the key and value alive. So the table -- should contain a weak pointer to the key, not an ordinary pointer. The -- pointer to the value must not be weak, because the only reference to -- the value might indeed be from the memo table. -- -- So it looks as if the memo table will keep all its values alive for -- ever. One way to solve this is to purge the table occasionally, by -- deleting entries whose keys have died. -- -- The weak pointers in this library support another approach, called -- finalization. When the key referred to by a weak pointer dies, -- the storage manager arranges to run a programmer-specified finalizer. -- In the case of memo tables, for example, the finalizer could remove -- the key/value pair from the memo table. -- -- Another difficulty with the memo table is that the value of a -- key/value pair might itself contain a pointer to the key. So the memo -- table keeps the value alive, which keeps the key alive, even though -- there may be no other references to the key so both should die. The -- weak pointers in this library provide a slight generalisation of the -- basic weak-pointer idea, in which each weak pointer actually contains -- both a key and a value. module System.Mem.Weak -- | A weak pointer object with a key and a value. The value has type -- v. -- -- A weak pointer expresses a relationship between two objects, the -- key and the value: if the key is considered to be alive -- by the garbage collector, then the value is also alive. A reference -- from the value to the key does not keep the key alive. -- -- A weak pointer may also have a finalizer of type IO (); if it -- does, then the finalizer will be run at most once, at a time after the -- key has become unreachable by the program ("dead"). The storage -- manager attempts to run the finalizer(s) for an object soon after the -- object dies, but promptness is not guaranteed. -- -- It is not guaranteed that a finalizer will eventually run, and no -- attempt is made to run outstanding finalizers when the program exits. -- Therefore finalizers should not be relied on to clean up resources - -- other methods (eg. exception handlers) should be employed, possibly in -- addition to finalizers. -- -- References from the finalizer to the key are treated in the same way -- as references from the value to the key: they do not keep the key -- alive. A finalizer may therefore ressurrect the key, perhaps by -- storing it in the same data structure. -- -- The finalizer, and the relationship between the key and the value, -- exist regardless of whether the program keeps a reference to the -- Weak object or not. -- -- There may be multiple weak pointers with the same key. In this case, -- the finalizers for each of these weak pointers will all be run in some -- arbitrary order, or perhaps concurrently, when the key dies. If the -- programmer specifies a finalizer that assumes it has the only -- reference to an object (for example, a file that it wishes to close), -- then the programmer must ensure that there is only one such finalizer. -- -- If there are no other threads to run, the runtime system will check -- for runnable finalizers before declaring the system to be deadlocked. -- -- WARNING: weak pointers to ordinary non-primitive Haskell types are -- particularly fragile, because the compiler is free to optimise away or -- duplicate the underlying data structure. Therefore attempting to place -- a finalizer on an ordinary Haskell type may well result in the -- finalizer running earlier than you expected. This is not a problem for -- caches and memo tables where early finalization is benign. -- -- Finalizers can be used reliably for types that are created -- explicitly and have identity, such as IORef and -- MVar. However, to place a finalizer on one of these types, -- you should use the specific operation provided for that type, e.g. -- mkWeakIORef and addMVarFinalizer respectively (the -- non-uniformity is accidental). These operations attach the finalizer -- to the primitive object inside the box (e.g. MutVar# in the -- case of IORef), because attaching the finalizer to the box -- itself fails when the outer box is optimised away by the compiler. data Weak v -- | Establishes a weak pointer to k, with value v and a -- finalizer. -- -- This is the most general interface for building a weak pointer. mkWeak :: k -> v -> Maybe (IO ()) -> IO (Weak v) -- | Dereferences a weak pointer. If the key is still alive, then -- Just v is returned (where v is the -- value in the weak pointer), otherwise Nothing is -- returned. -- -- The return value of deRefWeak depends on when the garbage -- collector runs, hence it is in the IO monad. deRefWeak :: Weak v -> IO (Maybe v) -- | Causes a the finalizer associated with a weak pointer to be run -- immediately. finalize :: Weak v -> IO () -- | A specialised version of mkWeak, where the key and the value -- are the same object: -- --
--   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; use the specialised version -- addForeignPtrFinalizer instead. For discussion see the -- Weak type. . 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)) -- | Stable names are a way of performing fast (O(1)), not-quite-exact -- comparison between objects. -- -- Stable names solve the following problem: suppose you want to build a -- hash table with Haskell objects as keys, but you want to use pointer -- equality for comparison; maybe because the keys are large and hashing -- would be slow, or perhaps because the keys are infinite in size. We -- can't build a hash table using the address of the object as the key, -- because objects get moved around by the garbage collector, meaning a -- re-hash would be necessary after every garbage collection. module System.Mem.StableName -- | An abstract name for an object, that supports equality and hashing. -- -- Stable names have the following property: -- -- -- -- The reverse is not necessarily true: if two stable names are not -- equal, then the objects they name may still be equal. Note in -- particular that makeStableName may return a different -- StableName after an object is evaluated. -- -- Stable Names are similar to Stable Pointers -- (Foreign.StablePtr), but differ in the following ways: -- -- data StableName a -- | Makes a StableName for an arbitrary object. The object passed -- as the first argument is not evaluated by makeStableName. makeStableName :: a -> IO (StableName a) -- | Convert a StableName to an Int. The Int returned -- is not necessarily unique; several StableNames may map to the -- same Int (in practice however, the chances of this are small, -- so the result of hashStableName makes a good hash key). hashStableName :: StableName a -> Int -- | Equality on StableName that does not require that the types of -- the arguments match. eqStableName :: StableName a -> StableName b -> Bool instance GHC.Classes.Eq (System.Mem.StableName.StableName a) -- | Memory-related system things. module System.Mem -- | Triggers an immediate major garbage collection. performGC :: IO () -- | Triggers an immediate major garbage collection. performMajorGC :: IO () -- | Triggers an immediate minor garbage collection. performMinorGC :: IO () -- | Every thread has an allocation counter that tracks how much memory has -- been allocated by the thread. The counter is initialized to zero, and -- setAllocationCounter sets the current value. The allocation -- counter counts *down*, so in the absence of a call to -- setAllocationCounter its value is the negation of the number of -- bytes of memory allocated by the thread. -- -- There are two things that you can do with this counter: -- -- -- -- Allocation accounting is accurate only to about 4Kbytes. setAllocationCounter :: Int64 -> IO () -- | Return the current value of the allocation counter for the current -- thread. getAllocationCounter :: IO Int64 -- | Enables the allocation counter to be treated as a limit for the -- current thread. When the allocation limit is enabled, if the -- allocation counter counts down below zero, the thread will be sent the -- AllocationLimitExceeded asynchronous exception. When this -- happens, the counter is reinitialised (by default to 100K, but tunable -- with the +RTS -xq option) so that it can handle the exception -- and perform any necessary clean up. If it exhausts this additional -- allowance, another AllocationLimitExceeded exception is sent, -- and so forth. Like other asynchronous exceptions, the -- AllocationLimitExceeded exception is deferred while the thread -- is inside mask or an exception handler in catch. -- -- Note that memory allocation is unrelated to live memory, also -- known as heap residency. A thread can allocate a large amount -- of memory and retain anything between none and all of it. It is better -- to think of the allocation limit as a limit on CPU time, rather -- than a limit on memory. -- -- Compared to using timeouts, allocation limits don't count time spent -- blocked or in foreign calls. enableAllocationLimit :: IO () -- | Disable allocation limit processing for the current thread. disableAllocationLimit :: IO () -- | Information about the characteristics of the host system lucky enough -- to run your program. module System.Info -- | The operating system on which the program is running. os :: String -- | The machine architecture on which the program is running. arch :: String -- | The Haskell implementation with which the program was compiled or is -- being interpreted. compilerName :: String -- | The version of compilerName with which the program was compiled -- or is being interpreted. compilerVersion :: Version -- | Exiting the program. module System.Exit -- | Defines the exit codes that a program can return. data ExitCode -- | indicates successful termination; ExitSuccess :: ExitCode -- | indicates program failure with an exit code. The exact interpretation -- of the code is operating-system dependent. In particular, some values -- may be prohibited (e.g. 0 on a POSIX-compliant system). ExitFailure :: Int -> ExitCode -- | Computation exitWith code throws ExitCode -- code. Normally this terminates the program, returning -- code to the program's caller. -- -- On program termination, the standard Handles stdout and -- stderr are flushed automatically; any other buffered -- Handles need to be flushed manually, otherwise the buffered -- data will be discarded. -- -- A program that fails in any other way is treated as if it had called -- exitFailure. A program that terminates successfully without -- calling exitWith explicitly is treated as if it had called -- exitWith ExitSuccess. -- -- As an ExitCode is not an IOError, exitWith -- bypasses the error handling in the IO monad and cannot be -- intercepted by catch from the Prelude. However it is a -- SomeException, and can be caught using the functions of -- Control.Exception. This means that cleanup computations added -- with bracket (from Control.Exception) are also executed -- properly on exitWith. -- -- Note: in GHC, exitWith should be called from the main program -- thread in order to exit the process. When called from another thread, -- exitWith will throw an ExitException as normal, but -- the exception will not cause the process itself to exit. exitWith :: ExitCode -> IO a -- | The computation exitFailure is equivalent to exitWith -- (ExitFailure exitfail), where -- exitfail is implementation-dependent. exitFailure :: IO a -- | The computation exitSuccess is equivalent to exitWith -- ExitSuccess, It terminates the program successfully. exitSuccess :: IO a -- | Write given error message to stderr and terminate with -- exitFailure. die :: String -> IO a -- | Miscellaneous information about the system environment. module System.Environment -- | Computation getArgs returns a list of the program's command -- line arguments (not including the program name). getArgs :: IO [String] -- | Computation getProgName returns the name of the program as it -- was invoked. -- -- However, this is hard-to-impossible to implement on some non-Unix -- OSes, so instead, for maximum portability, we just return the leafname -- of the program as invoked. Even then there are some differences -- between platforms: on Windows, for example, a program invoked as foo -- is probably really FOO.EXE, and that is what -- getProgName will return. getProgName :: IO String -- | Returns the absolute pathname of the current executable. -- -- Note that for scripts and interactive sessions, this is the path to -- the interpreter (e.g. ghci.) getExecutablePath :: IO FilePath -- | Computation getEnv var returns the value of the -- environment variable var. For the inverse, POSIX users can -- use putEnv. -- -- This computation may fail with: -- -- getEnv :: String -> IO String -- | Return the value of the environment variable var, or -- Nothing if there is no such value. -- -- For POSIX users, this is equivalent to getEnv. lookupEnv :: String -> IO (Maybe String) -- | setEnv name value sets the specified environment variable to -- value. -- -- On Windows setting an environment variable to the empty string -- removes that environment variable from the environment. For the sake -- of compatibility we adopt that behavior. In particular -- --
--   setEnv name ""
--   
-- -- has the same effect as -- --
--   unsetEnv name
--   
-- -- If you don't care about Windows support and want to set an environment -- variable to the empty string use System.Posix.Env.setEnv from -- the unix package instead. -- -- Throws IOException if name is the empty string or -- contains an equals sign. setEnv :: String -> String -> IO () -- | unsetEnv name removes the specified environment variable from -- the environment of the current process. -- -- Throws IOException if name is the empty string or -- contains an equals sign. unsetEnv :: String -> IO () -- | withArgs args act - while executing action -- act, have getArgs return args. withArgs :: [String] -> IO a -> IO a -- | withProgName name act - while executing action -- act, have getProgName return name. withProgName :: String -> IO a -> IO a -- | getEnvironment retrieves the entire environment as a list of -- (key,value) pairs. -- -- If an environment entry does not contain an '=' character, -- the key is the whole entry and the value is the -- empty string. getEnvironment :: IO [(String, String)] -- | This library provides facilities for parsing the command-line options -- in a standalone program. It is essentially a Haskell port of the GNU -- getopt library. module System.Console.GetOpt -- | Process the command-line, and return the list of values that matched -- (and those that didn't). The arguments are: -- -- -- -- getOpt returns a triple consisting of the option arguments, a -- list of non-options, and a list of error messages. getOpt :: ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String]) -- | This is almost the same as getOpt, but returns a quadruple -- consisting of the option arguments, a list of non-options, a list of -- unrecognized options, and a list of error messages. getOpt' :: ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String], [String]) -- | Return a string describing the usage of a command, derived from the -- header (first argument) and the options described by the second -- argument. usageInfo :: String -> [OptDescr a] -> String -- | What to do with options following non-options data ArgOrder a -- | no option processing after first non-option RequireOrder :: ArgOrder a -- | freely intersperse options and non-options Permute :: ArgOrder a -- | wrap non-options into options ReturnInOrder :: (String -> a) -> ArgOrder a -- | Each OptDescr describes a single option. -- -- The arguments to Option are: -- -- data OptDescr a Option :: [Char] -> [String] -> (ArgDescr a) -> String -> OptDescr a -- | Describes whether an option takes an argument or not, and if so how -- the argument is injected into a value of type a. data ArgDescr a -- | no argument expected NoArg :: a -> ArgDescr a -- | option requires argument ReqArg :: (String -> a) -> String -> ArgDescr a -- | optional argument OptArg :: (Maybe String -> a) -> String -> ArgDescr a instance GHC.Base.Functor System.Console.GetOpt.OptDescr instance GHC.Base.Functor System.Console.GetOpt.ArgDescr instance GHC.Base.Functor System.Console.GetOpt.ArgOrder -- | The standard CPUTime library. module System.CPUTime -- | Computation getCPUTime returns the number of picoseconds CPU -- time used by the current program. The precision of this result is -- implementation-dependent. getCPUTime :: IO Integer -- | The cpuTimePrecision constant is the smallest measurable -- difference in CPU time that the implementation can record, and is -- given as an integral number of picoseconds. cpuTimePrecision :: Integer -- | This module defines the HasField class used by the -- OverloadedRecordFields extension. See the -- <https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields -- wiki page> for more details. module GHC.Records -- | Constraint representing the fact that the field x belongs to -- the record type r and has field type a. This will be -- solved automatically, but manual instances may be provided as well. class HasField (x :: k) r a | x r -> a -- | Selector function to extract the field from the record. getField :: HasField x r a => r -> a -- | This module defines the IsLabel class is used by the -- OverloadedLabels extension. See the wiki page for more -- details. -- -- When OverloadedLabels is enabled, if GHC sees an occurrence -- of the overloaded label syntax #foo, it is replaced with -- --
--   fromLabel @"foo" :: alpha
--   
-- -- plus a wanted constraint IsLabel "foo" alpha. -- -- Note that if RebindableSyntax is enabled, the desugaring of -- overloaded label syntax will make use of whatever fromLabel -- is in scope. module GHC.OverloadedLabels class IsLabel (x :: Symbol) a fromLabel :: IsLabel x a => a -- | 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 GHC.Classes.Ord Data.Unique.Unique instance GHC.Classes.Eq Data.Unique.Unique -- | Mutable references in the (strict) ST monad. module Data.STRef -- | a value of type STRef s a is a mutable variable in state -- thread s, containing a value of type a data STRef s a -- | Build a new STRef in the current state thread newSTRef :: a -> ST s (STRef s a) -- | Read the value of an STRef readSTRef :: STRef s a -> ST s a -- | Write a new value into an STRef writeSTRef :: STRef s a -> a -> ST s () -- | Mutate the contents of an STRef. -- -- Be warned that modifySTRef does not apply the function -- strictly. This means if the program calls modifySTRef many -- times, but seldomly uses the value, thunks will pile up in memory -- resulting in a space leak. This is a common mistake made when using an -- STRef as a counter. For example, the following will leak memory and -- likely produce a stack overflow: -- --
--   print $ runST $ do
--       ref <- newSTRef 0
--       replicateM_ 1000000 $ modifySTRef ref (+1)
--       readSTRef ref
--   
-- -- To avoid this problem, use modifySTRef' instead. modifySTRef :: STRef s a -> (a -> a) -> ST s () -- | Strict version of modifySTRef modifySTRef' :: STRef s a -> (a -> a) -> ST s () -- | Mutable references in the (strict) ST monad (re-export of -- Data.STRef) module Data.STRef.Strict -- | Standard functions on rational numbers module Data.Ratio -- | Rational numbers, with numerator and denominator of some -- Integral type. data Ratio a -- | 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 -- | Forms the ratio of two integral numbers. (%) :: (Integral a) => a -> a -> Ratio a infixl 7 % -- | Extract the numerator of the ratio in reduced form: the numerator and -- denominator have no common factor and the denominator is positive. numerator :: Ratio a -> a -- | Extract the denominator of the ratio in reduced form: the numerator -- and denominator have no common factor and the denominator is positive. denominator :: Ratio a -> a -- | approxRational, applied to two real fractional numbers -- x and epsilon, returns the simplest rational number -- within epsilon of x. A rational number y is -- said to be simpler than another y' if -- -- -- -- Any real interval contains a unique simplest rational; in particular, -- note that 0/1 is the simplest rational of all. approxRational :: (RealFrac a) => a -> a -> Rational -- | Basic kinds module Data.Kind -- | The kind of types with values. For example Int :: Type. type Type = * -- | The kind of constraints, like Show a data Constraint :: * -- | A backward-compatible (pre-GHC 8.0) synonym for Type type * = * -- | A unicode backward-compatible (pre-GHC 8.0) synonym for Type type ★ = * -- | 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). Ix uses row-major order. 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: -- -- class (Ord a) => Ix a -- | The list of values in the subrange defined by a bounding pair. range :: Ix a => (a, a) -> [a] -- | The position of a subscript in the subrange. index :: Ix a => (a, a) -> a -> Int -- | Returns True the given subscript lies in the range defined the -- bounding pair. inRange :: Ix a => (a, a) -> a -> Bool -- | The size of the subrange defined by a bounding pair. rangeSize :: Ix a => (a, a) -> Int -- | 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 allows an ST computation to be -- deferred lazily. When passed a value of type ST a, the -- ST computation will only be performed when the value of the -- a is demanded. unsafeInterleaveST :: ST s a -> ST s a -- | unsafeDupableInterleaveST allows an ST computation to be -- deferred lazily. When passed a value of type ST a, the -- ST computation will only be performed when the value of the -- a is demanded. -- -- The computation may be performed multiple times by different threads, -- possibly at the same time. To prevent this, use -- unsafeInterleaveST instead. unsafeDupableInterleaveST :: ST s a -> ST s a -- | Convert an IO action to an ST action. This relies on -- IO and ST having the same representation modulo the -- constraint on the type of the state. unsafeIOToST :: IO a -> ST s a -- | Convert an ST action to an IO action. This relies on -- IO and ST having the same representation modulo the -- constraint on the type of the state. -- -- For an example demonstrating why this is unsafe, see -- https://mail.haskell.org/pipermail/haskell-cafe/2009-April/060719.html 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. -- -- Safe API Only. -- | Deprecated: Safe is now the default, please use Control.Monad.ST -- instead 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 -- -- -- -- It serves to keep the internal states of different invocations of -- runST separate from each other and from invocations of -- stToIO. -- -- The >>= and >> operations are strict in the -- state (though not in values stored in the state). For example, -- --
--   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 :: * -- | Embed a strict state transformer in an IO action. 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. -- -- References (variables) that can be used within the ST monad -- are provided by Data.STRef, and arrays are provided by -- Data.Array.ST. 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 -- -- -- -- It serves to keep the internal states of different invocations of -- runST separate from each other and from invocations of -- stToIO. -- -- The >>= and >> operations are strict in the -- state (though not in values stored in the state). For example, -- --
--   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 :: * -- | Embed a strict state transformer in an IO action. 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 -- | The strict ST monad (re-export of Control.Monad.ST) module Control.Monad.ST.Strict -- | 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. -- -- Unsafe API. module Control.Monad.ST.Lazy.Unsafe unsafeInterleaveST :: ST s a -> ST s a unsafeIOToST :: IO a -> ST s 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. -- | Deprecated: Safe is now the default, please use -- Control.Monad.ST.Lazy instead 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 -- -- -- -- It serves to keep the internal states of different invocations of -- runST separate from each other and from invocations of -- stToIO. -- -- The >>= and >> operations are not strict in -- the state. For example, -- --
--   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 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. module Control.Monad.ST.Lazy -- | 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 -- -- -- -- It serves to keep the internal states of different invocations of -- runST separate from each other and from invocations of -- stToIO. -- -- The >>= and >> operations are not strict in -- the state. For example, -- --
--   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 -- | Mutable references in the lazy ST monad. module Data.STRef.Lazy -- | a value of type STRef s a is a mutable variable in state -- thread s, containing a value of type a data STRef s a newSTRef :: a -> ST s (STRef s a) readSTRef :: STRef s a -> ST s a writeSTRef :: STRef s a -> a -> ST s () modifySTRef :: STRef s a -> (a -> a) -> ST s () -- | This module is DEPRECATED and will be removed in the future! -- -- Functor and Monad instances for (->) r and -- Functor instances for (,) a and Either -- a. -- | Deprecated: This module now contains no instances and will be -- removed in the future 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 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 -- | 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. -- -- Instances of Monad should satisfy the following laws: -- -- -- -- Furthermore, the Monad and Applicative operations should -- relate as follows: -- -- -- -- The above laws imply: -- -- -- -- and that pure and (<*>) satisfy the applicative -- functor laws. -- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Applicative m => Monad m -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. (>>=) :: forall a b. Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. (>>) :: forall a b. Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a -- | Fail with a message. This operation is not part of the mathematical -- definition of a monad, but is invoked on pattern-match failure in a -- do expression. -- -- As part of the MonadFail proposal (MFP), this function is moved to its -- own class MonadFail (see Control.Monad.Fail for more -- details). The definition here will be removed in a future release. fail :: Monad m => String -> m a -- | Class of monads based on IO. module Control.Monad.IO.Class -- | Monads in which IO computations may be embedded. Any monad -- built by applying a sequence of monad transformers to the IO -- monad will be an instance of this class. -- -- Instances should satisfy the following laws, which state that -- liftIO is a transformer of monads: -- -- class (Monad m) => MonadIO m -- | Lift a computation from the IO monad. liftIO :: MonadIO m => IO a -> m a instance Control.Monad.IO.Class.MonadIO GHC.Types.IO -- | 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 -- | Statistics about runtime activity since the start of the program. This -- is a mirror of the C struct RTSStats in RtsAPI.h data RTSStats RTSStats :: Word32 -> Word32 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> RtsTime -> RtsTime -> RtsTime -> RtsTime -> RtsTime -> RtsTime -> GCDetails -> RTSStats -- | Total number of GCs [gcs] :: RTSStats -> Word32 -- | Total number of major (oldest generation) GCs [major_gcs] :: RTSStats -> Word32 -- | Total bytes allocated [allocated_bytes] :: RTSStats -> Word64 -- | Maximum live data (including large objects + compact regions) [max_live_bytes] :: RTSStats -> Word64 -- | Maximum live data in large objects [max_large_objects_bytes] :: RTSStats -> Word64 -- | Maximum live data in compact regions [max_compact_bytes] :: RTSStats -> Word64 -- | Maximum slop [max_slop_bytes] :: RTSStats -> Word64 -- | Maximum memory in use by the RTS [max_mem_in_use_bytes] :: RTSStats -> Word64 -- | Sum of live bytes across all major GCs. Divided by major_gcs gives the -- average live data over the lifetime of the program. [cumulative_live_bytes] :: RTSStats -> Word64 -- | Sum of copied_bytes across all GCs [copied_bytes] :: RTSStats -> Word64 -- | Sum of copied_bytes across all parallel GCs [par_copied_bytes] :: RTSStats -> Word64 -- | Sum of par_max_copied_bytes across all parallel GCs [cumulative_par_max_copied_bytes] :: RTSStats -> Word64 -- | Total CPU time used by the mutator [mutator_cpu_ns] :: RTSStats -> RtsTime -- | Total elapsed time used by the mutator [mutator_elapsed_ns] :: RTSStats -> RtsTime -- | Total CPU time used by the GC [gc_cpu_ns] :: RTSStats -> RtsTime -- | Total elapsed time used by the GC [gc_elapsed_ns] :: RTSStats -> RtsTime -- | Total CPU time (at the previous GC) [cpu_ns] :: RTSStats -> RtsTime -- | Total elapsed time (at the previous GC) [elapsed_ns] :: RTSStats -> RtsTime -- | Details about the most recent GC [gc] :: RTSStats -> GCDetails -- | Statistics about a single GC. This is a mirror of the C struct -- GCDetails in RtsAPI.h, with the field prefixed with -- gc_ to avoid collisions with RTSStats. data GCDetails GCDetails :: Word32 -> Word32 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> RtsTime -> RtsTime -> RtsTime -> GCDetails -- | The generation number of this GC [gcdetails_gen] :: GCDetails -> Word32 -- | Number of threads used in this GC [gcdetails_threads] :: GCDetails -> Word32 -- | Number of bytes allocated since the previous GC [gcdetails_allocated_bytes] :: GCDetails -> Word64 -- | Total amount of live data in the heap (incliudes large + compact data) [gcdetails_live_bytes] :: GCDetails -> Word64 -- | Total amount of live data in large objects [gcdetails_large_objects_bytes] :: GCDetails -> Word64 -- | Total amount of live data in compact regions [gcdetails_compact_bytes] :: GCDetails -> Word64 -- | Total amount of slop (wasted memory) [gcdetails_slop_bytes] :: GCDetails -> Word64 -- | Total amount of memory in use by the RTS [gcdetails_mem_in_use_bytes] :: GCDetails -> Word64 -- | Total amount of data copied during this GC [gcdetails_copied_bytes] :: GCDetails -> Word64 -- | In parallel GC, the max amount of data copied by any one thread [gcdetails_par_max_copied_bytes] :: GCDetails -> Word64 -- | The time elapsed during synchronisation before GC [gcdetails_sync_elapsed_ns] :: GCDetails -> RtsTime -- | The CPU time used during GC itself [gcdetails_cpu_ns] :: GCDetails -> RtsTime -- | The time elapsed during GC itself [gcdetails_elapsed_ns] :: GCDetails -> RtsTime -- | Time values from the RTS, using a fixed resolution of nanoseconds. type RtsTime = Int64 getRTSStats :: IO RTSStats -- | Returns whether GC stats have been enabled (with +RTS -T, for -- example). getRTSStatsEnabled :: IO Bool -- | Statistics about memory usage and the garbage collector. Apart from -- currentBytesUsed and currentBytesSlop all are cumulative -- values since the program started. -- | Deprecated: Use RTSStats instead. This will be removed in GHC -- 8.4.1 data GCStats -- | Deprecated: Use RTSStats instead. This will be removed in GHC -- 8.4.1 GCStats :: !Int64 -> !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 (any generation, major and -- minor) [numGcs] :: GCStats -> !Int64 -- | Maximum number of live bytes seen so far [maxBytesUsed] :: GCStats -> !Int64 -- | Number of byte usage samples taken, or equivalently the number of -- major GCs performed. [numByteUsageSamples] :: GCStats -> !Int64 -- | 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). [cumulativeBytesUsed] :: GCStats -> !Int64 -- | Number of bytes copied during GC [bytesCopied] :: GCStats -> !Int64 -- | Number of live bytes at the end of the last major GC [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 [peakMegabytesAllocated] :: GCStats -> !Int64 -- | Number of allocated megablocks [mblocksAllocated] :: 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 [wallSeconds] :: GCStats -> !Double -- | 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. [parTotBytesCopied] :: GCStats -> !Int64 -- | Sum of number of bytes copied each GC by the most active GC thread -- each GC. The ratio of parTotBytesCopied 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. -- | Deprecated: Use getRTSStats instead. This will be removed in GHC -- 8.4.1 getGCStats :: IO GCStats -- | Deprecated: use getRTSStatsEnabled instead. This will be removed in -- GHC 8.4.1 getGCStatsEnabled :: IO Bool instance GHC.Read.Read GHC.Stats.GCStats instance GHC.Show.Show GHC.Stats.GCStats instance GHC.Show.Show GHC.Stats.RTSStats instance GHC.Read.Read GHC.Stats.RTSStats instance GHC.Show.Show GHC.Stats.GCDetails instance GHC.Read.Read GHC.Stats.GCDetails -- | Accessors to GHC RTS flags. Descriptions of flags can be seen in -- GHC User's Guide, or by running RTS help message using +RTS -- --help. module GHC.RTS.Flags -- | Time is defined as a StgWord64 in -- stg/Types.h type RtsTime = Word64 -- | Parameters of the runtime system data RTSFlags RTSFlags :: GCFlags -> ConcFlags -> MiscFlags -> DebugFlags -> CCFlags -> ProfFlags -> TraceFlags -> TickyFlags -> ParFlags -> RTSFlags [gcFlags] :: RTSFlags -> GCFlags [concurrentFlags] :: RTSFlags -> ConcFlags [miscFlags] :: RTSFlags -> MiscFlags [debugFlags] :: RTSFlags -> DebugFlags [costCentreFlags] :: RTSFlags -> CCFlags [profilingFlags] :: RTSFlags -> ProfFlags [traceFlags] :: RTSFlags -> TraceFlags [tickyFlags] :: RTSFlags -> TickyFlags [parFlags] :: RTSFlags -> ParFlags -- | Should we produce a summary of the garbage collector statistics after -- the program has exited? data GiveGCStats NoGCStats :: GiveGCStats CollectGCStats :: GiveGCStats OneLineGCStats :: GiveGCStats SummaryGCStats :: GiveGCStats VerboseGCStats :: GiveGCStats -- | Parameters of the garbage collector. data GCFlags GCFlags :: Maybe FilePath -> GiveGCStats -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Bool -> Double -> Double -> Word32 -> Bool -> Bool -> Double -> Bool -> Bool -> RtsTime -> Bool -> Word -> Word -> Bool -> Word -> GCFlags [statsFile] :: GCFlags -> Maybe FilePath [giveStats] :: GCFlags -> GiveGCStats [maxStkSize] :: GCFlags -> Word32 [initialStkSize] :: GCFlags -> Word32 [stkChunkSize] :: GCFlags -> Word32 [stkChunkBufferSize] :: GCFlags -> Word32 [maxHeapSize] :: GCFlags -> Word32 [minAllocAreaSize] :: GCFlags -> Word32 [largeAllocLim] :: GCFlags -> Word32 [nurseryChunkSize] :: GCFlags -> Word32 [minOldGenSize] :: GCFlags -> Word32 [heapSizeSuggestion] :: GCFlags -> Word32 [heapSizeSuggestionAuto] :: GCFlags -> Bool [oldGenFactor] :: GCFlags -> Double [pcFreeHeap] :: GCFlags -> Double [generations] :: GCFlags -> Word32 [squeezeUpdFrames] :: GCFlags -> Bool -- | True = "compact all the time" [compact] :: GCFlags -> Bool [compactThreshold] :: GCFlags -> Double -- | use "mostly mark-sweep" instead of copying for the oldest generation [sweep] :: GCFlags -> Bool [ringBell] :: GCFlags -> Bool [idleGCDelayTime] :: GCFlags -> RtsTime [doIdleGC] :: GCFlags -> Bool -- | address to ask the OS for memory [heapBase] :: GCFlags -> Word [allocLimitGrace] :: GCFlags -> Word [numa] :: GCFlags -> Bool [numaMask] :: GCFlags -> Word -- | Parameters concerning context switching data ConcFlags ConcFlags :: RtsTime -> Int -> ConcFlags [ctxtSwitchTime] :: ConcFlags -> RtsTime [ctxtSwitchTicks] :: ConcFlags -> Int -- | Miscellaneous parameters data MiscFlags MiscFlags :: RtsTime -> Bool -> Bool -> Word -> MiscFlags [tickInterval] :: MiscFlags -> RtsTime [installSignalHandlers] :: MiscFlags -> Bool [machineReadable] :: MiscFlags -> Bool -- | address to ask the OS for memory for the linker, 0 ==> off [linkerMemBase] :: MiscFlags -> Word -- | Flags to control debugging output & extra checking in various -- subsystems. data DebugFlags DebugFlags :: Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> DebugFlags -- | s [scheduler] :: DebugFlags -> Bool -- | i [interpreter] :: DebugFlags -> Bool -- | w [weak] :: DebugFlags -> Bool -- | G [gccafs] :: DebugFlags -> Bool -- | g [gc] :: DebugFlags -> Bool -- | b [block_alloc] :: DebugFlags -> Bool -- | S [sanity] :: DebugFlags -> Bool -- | t [stable] :: DebugFlags -> Bool -- | p [prof] :: DebugFlags -> Bool -- | l the object linker [linker] :: DebugFlags -> Bool -- | a [apply] :: DebugFlags -> Bool -- | m [stm] :: DebugFlags -> Bool -- | z stack squeezing & lazy blackholing [squeeze] :: DebugFlags -> Bool -- | c coverage [hpc] :: DebugFlags -> Bool -- | r [sparks] :: DebugFlags -> Bool -- | Should the RTS produce a cost-center summary? data DoCostCentres CostCentresNone :: DoCostCentres CostCentresSummary :: DoCostCentres CostCentresVerbose :: DoCostCentres CostCentresAll :: DoCostCentres CostCentresJSON :: DoCostCentres -- | Parameters pertaining to the cost-center profiler. data CCFlags CCFlags :: DoCostCentres -> Int -> Int -> CCFlags [doCostCentres] :: CCFlags -> DoCostCentres [profilerTicks] :: CCFlags -> Int [msecsPerTick] :: CCFlags -> Int -- | What sort of heap profile are we collecting? data DoHeapProfile NoHeapProfiling :: DoHeapProfile HeapByCCS :: DoHeapProfile HeapByMod :: DoHeapProfile HeapByDescr :: DoHeapProfile HeapByType :: DoHeapProfile HeapByRetainer :: DoHeapProfile HeapByLDV :: DoHeapProfile HeapByClosureType :: DoHeapProfile -- | Parameters of the cost-center profiler data ProfFlags ProfFlags :: DoHeapProfile -> RtsTime -> Word -> Bool -> Bool -> Word -> Word -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> ProfFlags [doHeapProfile] :: ProfFlags -> DoHeapProfile -- | time between samples [heapProfileInterval] :: ProfFlags -> RtsTime -- | ticks between samples (derived) [heapProfileIntervalTicks] :: ProfFlags -> Word [includeTSOs] :: ProfFlags -> Bool [showCCSOnException] :: ProfFlags -> Bool [maxRetainerSetSize] :: ProfFlags -> Word [ccsLength] :: ProfFlags -> Word [modSelector] :: ProfFlags -> Maybe String [descrSelector] :: ProfFlags -> Maybe String [typeSelector] :: ProfFlags -> Maybe String [ccSelector] :: ProfFlags -> Maybe String [ccsSelector] :: ProfFlags -> Maybe String [retainerSelector] :: ProfFlags -> Maybe String [bioSelector] :: ProfFlags -> Maybe String -- | Is event tracing enabled? data DoTrace -- | no tracing TraceNone :: DoTrace -- | send tracing events to the event log TraceEventLog :: DoTrace -- | send tracing events to stderr TraceStderr :: DoTrace -- | Parameters pertaining to event tracing data TraceFlags TraceFlags :: DoTrace -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> TraceFlags [tracing] :: TraceFlags -> DoTrace -- | show timestamp in stderr output [timestamp] :: TraceFlags -> Bool -- | trace scheduler events [traceScheduler] :: TraceFlags -> Bool -- | trace GC events [traceGc] :: TraceFlags -> Bool -- | trace spark events by a sampled method [sparksSampled] :: TraceFlags -> Bool -- | trace spark events 100% accurately [sparksFull] :: TraceFlags -> Bool -- | trace user events (emitted from Haskell code) [user] :: TraceFlags -> Bool -- | Parameters pertaining to ticky-ticky profiler data TickyFlags TickyFlags :: Bool -> Maybe FilePath -> TickyFlags [showTickyStats] :: TickyFlags -> Bool [tickyFile] :: TickyFlags -> Maybe FilePath -- | Parameters pertaining to parallelism data ParFlags ParFlags :: Word32 -> Bool -> Word32 -> Bool -> Word32 -> Bool -> Word32 -> Word32 -> Word32 -> Bool -> ParFlags [nCapabilities] :: ParFlags -> Word32 [migrate] :: ParFlags -> Bool [maxLocalSparks] :: ParFlags -> Word32 [parGcEnabled] :: ParFlags -> Bool [parGcGen] :: ParFlags -> Word32 [parGcLoadBalancingEnabled] :: ParFlags -> Bool [parGcLoadBalancingGen] :: ParFlags -> Word32 [parGcNoSyncWithIdle] :: ParFlags -> Word32 [parGcThreads] :: ParFlags -> Word32 [setAffinity] :: ParFlags -> Bool getRTSFlags :: IO RTSFlags getGCFlags :: IO GCFlags getConcFlags :: IO ConcFlags getMiscFlags :: IO MiscFlags getDebugFlags :: IO DebugFlags getCCFlags :: IO CCFlags getProfFlags :: IO ProfFlags getTraceFlags :: IO TraceFlags getTickyFlags :: IO TickyFlags getParFlags :: IO ParFlags instance GHC.Show.Show GHC.RTS.Flags.RTSFlags instance GHC.Show.Show GHC.RTS.Flags.ParFlags instance GHC.Show.Show GHC.RTS.Flags.TickyFlags instance GHC.Show.Show GHC.RTS.Flags.TraceFlags instance GHC.Show.Show GHC.RTS.Flags.DoTrace instance GHC.Show.Show GHC.RTS.Flags.ProfFlags instance GHC.Show.Show GHC.RTS.Flags.DoHeapProfile instance GHC.Show.Show GHC.RTS.Flags.CCFlags instance GHC.Show.Show GHC.RTS.Flags.DoCostCentres instance GHC.Show.Show GHC.RTS.Flags.DebugFlags instance GHC.Show.Show GHC.RTS.Flags.MiscFlags instance GHC.Show.Show GHC.RTS.Flags.ConcFlags instance GHC.Show.Show GHC.RTS.Flags.GCFlags instance GHC.Show.Show GHC.RTS.Flags.GiveGCStats instance GHC.Enum.Enum GHC.RTS.Flags.DoTrace instance GHC.Enum.Enum GHC.RTS.Flags.DoHeapProfile instance GHC.Enum.Enum GHC.RTS.Flags.DoCostCentres instance GHC.Enum.Enum GHC.RTS.Flags.GiveGCStats -- | Internals of the ExecutionStack module module GHC.ExecutionStack.Internal -- | Location information about an address from a backtrace. data Location Location :: String -> String -> Maybe SrcLoc -> Location [objectName] :: Location -> String [functionName] :: Location -> String [srcLoc] :: Location -> Maybe SrcLoc -- | A location in the original program source. data SrcLoc SrcLoc :: String -> Int -> Int -> SrcLoc [sourceFile] :: SrcLoc -> String [sourceLine] :: SrcLoc -> Int [sourceColumn] :: SrcLoc -> Int -- | The state of the execution stack data StackTrace -- | List the frames of a stack trace. stackFrames :: StackTrace -> Maybe [Location] -- | How many stack frames in the given StackTrace stackDepth :: StackTrace -> Int -- | Get an execution stack. collectStackTrace :: IO (Maybe StackTrace) -- | Render a stacktrace as a string showStackFrames :: [Location] -> ShowS -- | Free the cached debug data. invalidateDebugCache :: IO () -- | This is a module for efficient stack traces. This stack trace -- implementation is considered low overhead. Basic usage looks like -- this: -- --
--   import GHC.ExecutionStack
--   
--   myFunction :: IO ()
--   myFunction = do
--        putStrLn =<< showStackTrace
--   
-- -- Your GHC must have been built with libdw support for this to -- work. -- --
--   user@host:~$ ghc --info | grep libdw
--    ,("RTS expects libdw",YES)
--   
module GHC.ExecutionStack -- | Location information about an address from a backtrace. data Location Location :: String -> String -> Maybe SrcLoc -> Location [objectName] :: Location -> String [functionName] :: Location -> String [srcLoc] :: Location -> Maybe SrcLoc -- | A location in the original program source. data SrcLoc SrcLoc :: String -> Int -> Int -> SrcLoc [sourceFile] :: SrcLoc -> String [sourceLine] :: SrcLoc -> Int [sourceColumn] :: SrcLoc -> Int -- | Get a trace of the current execution stack state. -- -- Returns Nothing if stack trace support isn't available on -- host machine. getStackTrace :: IO (Maybe [Location]) -- | Get a string representation of the current execution stack state. showStackTrace :: IO (Maybe String) -- | 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 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 Control.Monad.Zip.MonadZip [] instance Control.Monad.Zip.MonadZip Data.Functor.Identity.Identity instance Control.Monad.Zip.MonadZip Data.Monoid.Dual instance Control.Monad.Zip.MonadZip Data.Monoid.Sum instance Control.Monad.Zip.MonadZip Data.Monoid.Product instance Control.Monad.Zip.MonadZip GHC.Base.Maybe instance Control.Monad.Zip.MonadZip Data.Monoid.First instance Control.Monad.Zip.MonadZip Data.Monoid.Last instance Control.Monad.Zip.MonadZip f => Control.Monad.Zip.MonadZip (Data.Monoid.Alt f) instance Control.Monad.Zip.MonadZip Data.Proxy.Proxy instance Control.Monad.Zip.MonadZip GHC.Generics.U1 instance Control.Monad.Zip.MonadZip GHC.Generics.Par1 instance Control.Monad.Zip.MonadZip f => Control.Monad.Zip.MonadZip (GHC.Generics.Rec1 f) instance Control.Monad.Zip.MonadZip f => Control.Monad.Zip.MonadZip (GHC.Generics.M1 i c f) instance (Control.Monad.Zip.MonadZip f, Control.Monad.Zip.MonadZip g) => Control.Monad.Zip.MonadZip (f GHC.Generics.:*: g) -- | Liftings of the Prelude classes Eq, Ord, Read and -- Show to unary and binary type constructors. -- -- These classes are needed to express the constraints on arguments of -- transformers in portable Haskell. Thus for a new transformer -- T, one might write instances like -- --
--   instance (Eq1 f) => Eq1 (T f) where ...
--   instance (Ord1 f) => Ord1 (T f) where ...
--   instance (Read1 f) => Read1 (T f) where ...
--   instance (Show1 f) => Show1 (T f) where ...
--   
-- -- If these instances can be defined, defining instances of the base -- classes is mechanical: -- --
--   instance (Eq1 f, Eq a) => Eq (T f a) where (==) = eq1
--   instance (Ord1 f, Ord a) => Ord (T f a) where compare = compare1
--   instance (Read1 f, Read a) => Read (T f a) where
--     readPrec     = readPrec1
--     readListPrec = readListPrecDefault
--   instance (Show1 f, Show a) => Show (T f a) where showsPrec = showsPrec1
--   
module Data.Functor.Classes -- | Lifting of the Eq class to unary type constructors. class Eq1 f -- | Lift an equality test through the type constructor. -- -- The function will usually be applied to an equality function, but the -- more general type ensures that the implementation uses it to compare -- elements of the first container with elements of the second. liftEq :: Eq1 f => (a -> b -> Bool) -> f a -> f b -> Bool -- | Lift the standard (==) function through the type -- constructor. eq1 :: (Eq1 f, Eq a) => f a -> f a -> Bool -- | Lifting of the Ord class to unary type constructors. class (Eq1 f) => Ord1 f -- | Lift a compare function through the type constructor. -- -- The function will usually be applied to a comparison function, but the -- more general type ensures that the implementation uses it to compare -- elements of the first container with elements of the second. liftCompare :: Ord1 f => (a -> b -> Ordering) -> f a -> f b -> Ordering -- | Lift the standard compare function through the type -- constructor. compare1 :: (Ord1 f, Ord a) => f a -> f a -> Ordering -- | Lifting of the Read class to unary type constructors. -- -- Both liftReadsPrec and liftReadPrec exist to match the -- interface provided in the Read type class, but it is -- recommended to implement Read1 instances using -- liftReadPrec as opposed to liftReadsPrec, since the -- former is more efficient than the latter. For example: -- --
--   instance Read1 T where
--     liftReadPrec     = ...
--     liftReadListPrec = liftReadListPrecDefault
--   
-- -- For more information, refer to the documentation for the Read -- class. class Read1 f -- | readsPrec function for an application of the type constructor -- based on readsPrec and readList functions for the -- argument type. liftReadsPrec :: Read1 f => (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) -- | readList function for an application of the type constructor -- based on readsPrec and readList functions for the -- argument type. The default implementation using standard list syntax -- is correct for most types. liftReadList :: Read1 f => (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] -- | readPrec function for an application of the type constructor -- based on readPrec and readListPrec functions for the -- argument type. liftReadPrec :: Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) -- | readListPrec function for an application of the type -- constructor based on readPrec and readListPrec functions -- for the argument type. -- -- The default definition uses liftReadList. Instances that define -- liftReadPrec should also define liftReadListPrec as -- liftReadListPrecDefault. liftReadListPrec :: Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec [f a] -- | Lift the standard readsPrec and readList functions -- through the type constructor. readsPrec1 :: (Read1 f, Read a) => Int -> ReadS (f a) -- | Lift the standard readPrec and readListPrec functions -- through the type constructor. readPrec1 :: (Read1 f, Read a) => ReadPrec (f a) -- | A possible replacement definition for the liftReadList method. -- This is only needed for Read1 instances where -- liftReadListPrec isn't defined as -- liftReadListPrecDefault. liftReadListDefault :: Read1 f => (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] -- | A possible replacement definition for the liftReadListPrec -- method, defined using liftReadPrec. liftReadListPrecDefault :: Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec [f a] -- | Lifting of the Show class to unary type constructors. class Show1 f -- | showsPrec function for an application of the type constructor -- based on showsPrec and showList functions for the -- argument type. liftShowsPrec :: Show1 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS -- | showList function for an application of the type constructor -- based on showsPrec and showList functions for the -- argument type. The default implementation using standard list syntax -- is correct for most types. liftShowList :: Show1 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS -- | Lift the standard showsPrec and showList functions -- through the type constructor. showsPrec1 :: (Show1 f, Show a) => Int -> f a -> ShowS -- | Lifting of the Eq class to binary type constructors. class Eq2 f -- | Lift equality tests through the type constructor. -- -- The function will usually be applied to equality functions, but the -- more general type ensures that the implementation uses them to compare -- elements of the first container with elements of the second. liftEq2 :: Eq2 f => (a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool -- | Lift the standard (==) function through the type -- constructor. eq2 :: (Eq2 f, Eq a, Eq b) => f a b -> f a b -> Bool -- | Lifting of the Ord class to binary type constructors. class (Eq2 f) => Ord2 f -- | Lift compare functions through the type constructor. -- -- The function will usually be applied to comparison functions, but the -- more general type ensures that the implementation uses them to compare -- elements of the first container with elements of the second. liftCompare2 :: Ord2 f => (a -> b -> Ordering) -> (c -> d -> Ordering) -> f a c -> f b d -> Ordering -- | Lift the standard compare function through the type -- constructor. compare2 :: (Ord2 f, Ord a, Ord b) => f a b -> f a b -> Ordering -- | Lifting of the Read class to binary type constructors. -- -- Both liftReadsPrec2 and liftReadPrec2 exist to match the -- interface provided in the Read type class, but it is -- recommended to implement Read2 instances using -- liftReadPrec2 as opposed to liftReadsPrec2, since the -- former is more efficient than the latter. For example: -- --
--   instance Read2 T where
--     liftReadPrec2     = ...
--     liftReadListPrec2 = liftReadListPrec2Default
--   
-- -- For more information, refer to the documentation for the Read -- class. @since 4.9.0.0 class Read2 f -- | readsPrec function for an application of the type constructor -- based on readsPrec and readList functions for the -- argument types. liftReadsPrec2 :: Read2 f => (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (f a b) -- | readList function for an application of the type constructor -- based on readsPrec and readList functions for the -- argument types. The default implementation using standard list syntax -- is correct for most types. liftReadList2 :: Read2 f => (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b] -- | readPrec function for an application of the type constructor -- based on readPrec and readListPrec functions for the -- argument types. liftReadPrec2 :: Read2 f => ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b) -- | readListPrec function for an application of the type -- constructor based on readPrec and readListPrec functions -- for the argument types. -- -- The default definition uses liftReadList2. Instances that -- define liftReadPrec2 should also define -- liftReadListPrec2 as liftReadListPrec2Default. liftReadListPrec2 :: Read2 f => ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b] -- | Lift the standard readsPrec function through the type -- constructor. readsPrec2 :: (Read2 f, Read a, Read b) => Int -> ReadS (f a b) -- | Lift the standard readPrec function through the type -- constructor. readPrec2 :: (Read2 f, Read a, Read b) => ReadPrec (f a b) -- | A possible replacement definition for the liftReadList2 method. -- This is only needed for Read2 instances where -- liftReadListPrec2 isn't defined as -- liftReadListPrec2Default. liftReadList2Default :: Read2 f => (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b] -- | A possible replacement definition for the liftReadListPrec2 -- method, defined using liftReadPrec2. liftReadListPrec2Default :: Read2 f => ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b] -- | Lifting of the Show class to binary type constructors. class Show2 f -- | showsPrec function for an application of the type constructor -- based on showsPrec and showList functions for the -- argument types. liftShowsPrec2 :: Show2 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> f a b -> ShowS -- | showList function for an application of the type constructor -- based on showsPrec and showList functions for the -- argument types. The default implementation using standard list syntax -- is correct for most types. liftShowList2 :: Show2 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [f a b] -> ShowS -- | Lift the standard showsPrec function through the type -- constructor. showsPrec2 :: (Show2 f, Show a, Show b) => Int -> f a b -> ShowS -- | readsData p d is a parser for datatypes where each -- alternative begins with a data constructor. It parses the constructor -- and passes it to p. Parsers for various constructors can be -- constructed with readsUnary, readsUnary1 and -- readsBinary1, and combined with mappend from the -- Monoid class. readsData :: (String -> ReadS a) -> Int -> ReadS a -- | readData p is a parser for datatypes where each -- alternative begins with a data constructor. It parses the constructor -- and passes it to p. Parsers for various constructors can be -- constructed with readUnaryWith and readBinaryWith, and -- combined with '(|)' from the Alternative class. readData :: ReadPrec a -> ReadPrec a -- | readsUnaryWith rp n c n' matches the name of a unary -- data constructor and then parses its argument using rp. readsUnaryWith :: (Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t -- | readUnaryWith rp n c' matches the name of a unary data -- constructor and then parses its argument using rp. readUnaryWith :: ReadPrec a -> String -> (a -> t) -> ReadPrec t -- | readsBinaryWith rp1 rp2 n c n' matches the name of a -- binary data constructor and then parses its arguments using -- rp1 and rp2 respectively. readsBinaryWith :: (Int -> ReadS a) -> (Int -> ReadS b) -> String -> (a -> b -> t) -> String -> ReadS t -- | readBinaryWith rp1 rp2 n c' matches the name of a -- binary data constructor and then parses its arguments using -- rp1 and rp2 respectively. readBinaryWith :: ReadPrec a -> ReadPrec b -> String -> (a -> b -> t) -> ReadPrec t -- | showsUnaryWith sp n d x produces the string -- representation of a unary data constructor with name n and -- argument x, in precedence context d. showsUnaryWith :: (Int -> a -> ShowS) -> String -> Int -> a -> ShowS -- | showsBinaryWith sp1 sp2 n d x y produces the string -- representation of a binary data constructor with name n and -- arguments x and y, in precedence context d. showsBinaryWith :: (Int -> a -> ShowS) -> (Int -> b -> ShowS) -> String -> Int -> a -> b -> ShowS -- | readsUnary n c n' matches the name of a unary data -- constructor and then parses its argument using readsPrec. -- | Deprecated: Use readsUnaryWith to define liftReadsPrec readsUnary :: (Read a) => String -> (a -> t) -> String -> ReadS t -- | readsUnary1 n c n' matches the name of a unary data -- constructor and then parses its argument using readsPrec1. -- | Deprecated: Use readsUnaryWith to define liftReadsPrec readsUnary1 :: (Read1 f, Read a) => String -> (f a -> t) -> String -> ReadS t -- | readsBinary1 n c n' matches the name of a binary data -- constructor and then parses its arguments using readsPrec1. -- | Deprecated: Use readsBinaryWith to define liftReadsPrec readsBinary1 :: (Read1 f, Read1 g, Read a) => String -> (f a -> g a -> t) -> String -> ReadS t -- | showsUnary n d x produces the string representation of -- a unary data constructor with name n and argument x, -- in precedence context d. -- | Deprecated: Use showsUnaryWith to define liftShowsPrec showsUnary :: (Show a) => String -> Int -> a -> ShowS -- | showsUnary1 n d x produces the string representation -- of a unary data constructor with name n and argument -- x, in precedence context d. -- | Deprecated: Use showsUnaryWith to define liftShowsPrec showsUnary1 :: (Show1 f, Show a) => String -> Int -> f a -> ShowS -- | showsBinary1 n d x y produces the string -- representation of a binary data constructor with name n and -- arguments x and y, in precedence context d. -- | Deprecated: Use showsBinaryWith to define liftShowsPrec showsBinary1 :: (Show1 f, Show1 g, Show a) => String -> Int -> f a -> g a -> ShowS instance Data.Functor.Classes.Show2 (,) instance GHC.Show.Show a => Data.Functor.Classes.Show1 ((,) a) instance Data.Functor.Classes.Show2 Data.Either.Either instance GHC.Show.Show a => Data.Functor.Classes.Show1 (Data.Either.Either a) instance Data.Functor.Classes.Show2 Data.Functor.Const.Const instance GHC.Show.Show a => Data.Functor.Classes.Show1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Read2 (,) instance GHC.Read.Read a => Data.Functor.Classes.Read1 ((,) a) instance Data.Functor.Classes.Read2 Data.Either.Either instance GHC.Read.Read a => Data.Functor.Classes.Read1 (Data.Either.Either a) instance Data.Functor.Classes.Read2 Data.Functor.Const.Const instance GHC.Read.Read a => Data.Functor.Classes.Read1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Ord2 (,) instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 ((,) a) instance Data.Functor.Classes.Ord2 Data.Either.Either instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 (Data.Either.Either a) instance Data.Functor.Classes.Ord2 Data.Functor.Const.Const instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Eq2 (,) instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 ((,) a) instance Data.Functor.Classes.Eq2 Data.Either.Either instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 (Data.Either.Either a) instance Data.Functor.Classes.Eq2 Data.Functor.Const.Const instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Show1 GHC.Base.Maybe instance Data.Functor.Classes.Show1 [] instance Data.Functor.Classes.Show1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Show1 Data.Proxy.Proxy instance Data.Functor.Classes.Read1 GHC.Base.Maybe instance Data.Functor.Classes.Read1 [] instance Data.Functor.Classes.Read1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Read1 Data.Proxy.Proxy instance Data.Functor.Classes.Ord1 GHC.Base.Maybe instance Data.Functor.Classes.Ord1 [] instance Data.Functor.Classes.Ord1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Ord1 Data.Proxy.Proxy instance Data.Functor.Classes.Eq1 GHC.Base.Maybe instance Data.Functor.Classes.Eq1 [] instance Data.Functor.Classes.Eq1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Eq1 Data.Proxy.Proxy module Data.Bifunctor -- | Formally, the class Bifunctor represents a bifunctor from -- Hask -> Hask. -- -- Intuitively it is a bifunctor where both the first and second -- arguments are covariant. -- -- You can define a Bifunctor by either defining bimap or -- by defining both first and second. -- -- If you supply bimap, you should ensure that: -- --
--   bimap id idid
--   
-- -- If you supply first and second, ensure: -- --
--   first idid
--   second idid
--   
-- -- If you supply both, you should also ensure: -- --
--   bimap f g ≡ first f . second g
--   
-- -- These ensure by parametricity: -- --
--   bimap  (f . g) (h . i) ≡ bimap f h . bimap g i
--   first  (f . g) ≡ first  f . first  g
--   second (f . g) ≡ second f . second g
--   
class Bifunctor p -- | Map over both arguments at the same time. -- --
--   bimap f g ≡ first f . second g
--   
bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d -- | Map covariantly over the first argument. -- --
--   first f ≡ bimap f id
--   
first :: Bifunctor p => (a -> b) -> p a c -> p b c -- | Map covariantly over the second argument. -- --
--   secondbimap id
--   
second :: Bifunctor p => (b -> c) -> p a b -> p a c instance Data.Bifunctor.Bifunctor (,) instance Data.Bifunctor.Bifunctor ((,,) x1) instance Data.Bifunctor.Bifunctor ((,,,) x1 x2) instance Data.Bifunctor.Bifunctor ((,,,,) x1 x2 x3) instance Data.Bifunctor.Bifunctor ((,,,,,) x1 x2 x3 x4) instance Data.Bifunctor.Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) instance Data.Bifunctor.Bifunctor Data.Either.Either instance Data.Bifunctor.Bifunctor Data.Functor.Const.Const instance Data.Bifunctor.Bifunctor (GHC.Generics.K1 i) module Data.Bifoldable -- | Bifoldable identifies foldable structures with two different -- varieties of elements (as opposed to Foldable, which has one -- variety of element). Common examples are Either and '(,)': -- --
--   instance Bifoldable Either where
--     bifoldMap f _ (Left  a) = f a
--     bifoldMap _ g (Right b) = g b
--   
--   instance Bifoldable (,) where
--     bifoldr f g z (a, b) = f a (g b z)
--   
-- -- A minimal Bifoldable definition consists of either -- bifoldMap or bifoldr. When defining more than this -- minimal set, one should ensure that the following identities hold: -- --
--   bifoldbifoldMap id id
--   bifoldMap f g ≡ bifoldr (mappend . f) (mappend . g) mempty
--   bifoldr f g z t ≡ appEndo (bifoldMap (Endo . f) (Endo . g) t) z
--   
-- -- If the type is also a Bifunctor instance, it should satisfy: -- --
--   'bifoldMap' f g ≡ 'bifold' . 'bimap' f g
--   
-- -- which implies that -- --
--   'bifoldMap' f g . 'bimap' h i ≡ 'bifoldMap' (f . h) (g . i)
--   
class Bifoldable p -- | Combines the elements of a structure using a monoid. -- --
--   bifoldbifoldMap id id
--   
bifold :: (Bifoldable p, Monoid m) => p m m -> m -- | Combines the elements of a structure, given ways of mapping them to a -- common monoid. -- --
--   bifoldMap f g
--        ≡ bifoldr (mappend . f) (mappend . g) mempty
--   
bifoldMap :: (Bifoldable p, Monoid m) => (a -> m) -> (b -> m) -> p a b -> m -- | Combines the elements of a structure in a right associative manner. -- Given a hypothetical function toEitherList :: p a b -> [Either -- a b] yielding a list of all elements of a structure in order, the -- following would hold: -- --
--   bifoldr f g z ≡ foldr (either f g) z . toEitherList
--   
bifoldr :: Bifoldable p => (a -> c -> c) -> (b -> c -> c) -> c -> p a b -> c -- | Combines the elments of a structure in a left associative manner. -- Given a hypothetical function toEitherList :: p a b -> [Either -- a b] yielding a list of all elements of a structure in order, the -- following would hold: -- --
--   bifoldl f g z
--        ≡ foldl (acc -> either (f acc) (g acc)) z . toEitherList
--   
-- -- Note that if you want an efficient left-fold, you probably want to use -- bifoldl' instead of bifoldl. The reason is that the -- latter does not force the "inner" results, resulting in a thunk chain -- which then must be evaluated from the outside-in. bifoldl :: Bifoldable p => (c -> a -> c) -> (c -> b -> c) -> c -> p a b -> c -- | As bifoldr, but strict in the result of the reduction functions -- at each step. bifoldr' :: Bifoldable t => (a -> c -> c) -> (b -> c -> c) -> c -> t a b -> c -- | A variant of bifoldr that has no base case, and thus may only -- be applied to non-empty structures. bifoldr1 :: Bifoldable t => (a -> a -> a) -> t a a -> a -- | Right associative monadic bifold over a structure. bifoldrM :: (Bifoldable t, Monad m) => (a -> c -> m c) -> (b -> c -> m c) -> c -> t a b -> m c -- | As bifoldl, but strict in the result of the reduction functions -- at each step. -- -- This ensures that each step of the bifold is forced to weak head -- normal form before being applied, avoiding the collection of thunks -- that would otherwise occur. This is often what you want to strictly -- reduce a finite structure to a single, monolithic result (e.g., -- bilength). bifoldl' :: Bifoldable t => (a -> b -> a) -> (a -> c -> a) -> a -> t b c -> a -- | A variant of bifoldl that has no base case, and thus may only -- be applied to non-empty structures. bifoldl1 :: Bifoldable t => (a -> a -> a) -> t a a -> a -- | Left associative monadic bifold over a structure. bifoldlM :: (Bifoldable t, Monad m) => (a -> b -> m a) -> (a -> c -> m a) -> a -> t b c -> m a -- | Map each element of a structure using one of two actions, evaluate -- these actions from left to right, and ignore the results. For a -- version that doesn't ignore the results, see bitraverse. bitraverse_ :: (Bifoldable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f () -- | As bitraverse_, but with the structure as the primary argument. -- For a version that doesn't ignore the results, see bifor. -- --
--   >>> > bifor_ ('a', "bc") print (print . reverse)
--   'a'
--   "cb"
--   
bifor_ :: (Bifoldable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f () -- | Alias for bitraverse_. bimapM_ :: (Bifoldable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f () -- | Alias for bifor_. biforM_ :: (Bifoldable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f () -- | Alias for biasum. bimsum :: (Bifoldable t, Alternative f) => t (f a) (f a) -> f a -- | Alias for bisequence_. bisequenceA_ :: (Bifoldable t, Applicative f) => t (f a) (f b) -> f () -- | Evaluate each action in the structure from left to right, and ignore -- the results. For a version that doesn't ignore the results, see -- bisequence. bisequence_ :: (Bifoldable t, Applicative f) => t (f a) (f b) -> f () -- | The sum of a collection of actions, generalizing biconcat. biasum :: (Bifoldable t, Alternative f) => t (f a) (f a) -> f a -- | Collects the list of elements of a structure, from left to right. biList :: Bifoldable t => t a a -> [a] -- | Test whether the structure is empty. binull :: Bifoldable t => t a b -> Bool -- | Returns the size/length of a finite structure as an Int. bilength :: Bifoldable t => t a b -> Int -- | Does the element occur in the structure? bielem :: (Bifoldable t, Eq a) => a -> t a a -> Bool -- | The largest element of a non-empty structure. bimaximum :: forall t a. (Bifoldable t, Ord a) => t a a -> a -- | The least element of a non-empty structure. biminimum :: forall t a. (Bifoldable t, Ord a) => t a a -> a -- | The bisum function computes the sum of the numbers of a -- structure. bisum :: (Bifoldable t, Num a) => t a a -> a -- | The biproduct function computes the product of the numbers of a -- structure. biproduct :: (Bifoldable t, Num a) => t a a -> a -- | Reduces a structure of lists to the concatenation of those lists. biconcat :: Bifoldable t => t [a] [a] -> [a] -- | Given a means of mapping the elements of a structure to lists, -- computes the concatenation of all such lists in order. biconcatMap :: Bifoldable t => (a -> [c]) -> (b -> [c]) -> t a b -> [c] -- | biand 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. biand :: Bifoldable t => t Bool Bool -> Bool -- | bior 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. bior :: Bifoldable t => t Bool Bool -> Bool -- | Determines whether any element of the structure satisfies its -- appropriate predicate argument. biany :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> Bool -- | Determines whether all elements of the structure satisfy their -- appropriate predicate argument. biall :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> Bool -- | The largest element of a non-empty structure with respect to the given -- comparison function. bimaximumBy :: Bifoldable t => (a -> a -> Ordering) -> t a a -> a -- | The least element of a non-empty structure with respect to the given -- comparison function. biminimumBy :: Bifoldable t => (a -> a -> Ordering) -> t a a -> a -- | binotElem is the negation of bielem. binotElem :: (Bifoldable t, Eq a) => a -> t a a -> Bool -- | The bifind 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. bifind :: Bifoldable t => (a -> Bool) -> t a a -> Maybe a instance Data.Bifoldable.Bifoldable (,) instance Data.Bifoldable.Bifoldable Data.Functor.Const.Const instance Data.Bifoldable.Bifoldable (GHC.Generics.K1 i) instance Data.Bifoldable.Bifoldable ((,,) x) instance Data.Bifoldable.Bifoldable ((,,,) x y) instance Data.Bifoldable.Bifoldable ((,,,,) x y z) instance Data.Bifoldable.Bifoldable ((,,,,,) x y z w) instance Data.Bifoldable.Bifoldable ((,,,,,,) x y z w v) instance Data.Bifoldable.Bifoldable Data.Either.Either module Data.Bitraversable -- | Bitraversable identifies bifunctorial data structures whose -- elements can be traversed in order, performing Applicative or -- Monad actions at each element, and collecting a result -- structure with the same shape. -- -- As opposed to Traversable data structures, which have one -- variety of element on which an action can be performed, -- Bitraversable data structures have two such varieties of -- elements. -- -- A definition of bitraverse must satisfy the following laws: -- -- -- -- where an applicative transformation is a function -- --
--   t :: (Applicative f, Applicative g) => f a -> g a
--   
-- -- preserving the Applicative operations: -- --
--   t (pure x) = pure x
--   t (f <*> x) = t f <*> t x
--   
-- -- and the identity functor Identity and composition functors -- Compose are defined as -- --
--   newtype Identity a = Identity { runIdentity :: a }
--   
--   instance Functor Identity where
--     fmap f (Identity x) = Identity (f x)
--   
--   instance Applicative Identity where
--     pure = Identity
--     Identity f <*> Identity x = Identity (f x)
--   
--   newtype Compose f g a = Compose (f (g a))
--   
--   instance (Functor f, Functor g) => Functor (Compose f g) where
--     fmap f (Compose x) = Compose (fmap (fmap f) x)
--   
--   instance (Applicative f, Applicative g) => Applicative (Compose f g) where
--     pure = Compose . pure . pure
--     Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
--   
-- -- Some simple examples are Either and '(,)': -- --
--   instance Bitraversable Either where
--     bitraverse f _ (Left x) = Left <$> f x
--     bitraverse _ g (Right y) = Right <$> g y
--   
--   instance Bitraversable (,) where
--     bitraverse f g (x, y) = (,) <$> f x <*> g y
--   
-- -- Bitraversable relates to its superclasses in the following -- ways: -- --
--   bimap f g ≡ runIdentity . bitraverse (Identity . f) (Identity . g)
--   bifoldMap f g = getConst . bitraverse (Const . f) (Const . g)
--   
-- -- These are available as bimapDefault and bifoldMapDefault -- respectively. class (Bifunctor t, Bifoldable t) => Bitraversable t -- | Evaluates the relevant functions at each element in the structure, -- running the action, and builds a new structure with the same shape, -- using the results produced from sequencing the actions. -- --
--   bitraverse f g ≡ bisequenceA . bimap f g
--   
-- -- For a version that ignores the results, see bitraverse_. bitraverse :: (Bitraversable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) -- | Alias for bisequence. bisequenceA :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b) -- | Sequences all the actions in a structure, building a new structure -- with the same shape using the results of the actions. For a version -- that ignores the results, see bisequence_. -- --
--   bisequencebitraverse id id
--   
bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b) -- | Alias for bitraverse. bimapM :: (Bitraversable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) -- | bifor is bitraverse with the structure as the first -- argument. For a version that ignores the results, see bifor_. bifor :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d) -- | Alias for bifor. biforM :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d) -- | The bimapAccumL function behaves like a combination of -- bimap and bifoldl; it traverses a structure from left to -- right, threading a state of type a and using the given -- actions to compute new elements for the structure. bimapAccumL :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e) -- | The bimapAccumR function behaves like a combination of -- bimap and bifoldl; it traverses a structure from right -- to left, threading a state of type a and using the given -- actions to compute new elements for the structure. bimapAccumR :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e) -- | A default definition of bimap in terms of the -- Bitraversable operations. -- --
--   bimapDefault f g ≡
--        runIdentity . bitraverse (Identity . f) (Identity . g)
--   
bimapDefault :: forall t a b c d. Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d -- | A default definition of bifoldMap in terms of the -- Bitraversable operations. -- --
--   bifoldMapDefault f g ≡
--       getConst . bitraverse (Const . f) (Const . g)
--   
bifoldMapDefault :: forall t m a b. (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m instance Data.Bitraversable.Bitraversable (,) instance Data.Bitraversable.Bitraversable ((,,) x) instance Data.Bitraversable.Bitraversable ((,,,) x y) instance Data.Bitraversable.Bitraversable ((,,,,) x y z) instance Data.Bitraversable.Bitraversable ((,,,,,) x y z w) instance Data.Bitraversable.Bitraversable ((,,,,,,) x y z w v) instance Data.Bitraversable.Bitraversable Data.Either.Either instance Data.Bitraversable.Bitraversable Data.Functor.Const.Const instance Data.Bitraversable.Bitraversable (GHC.Generics.K1 i) -- | This module provides scalable event notification for file descriptors -- and timeouts. -- -- This module should be considered GHC internal. -- -- module GHC.Event -- | The event manager state. data EventManager -- | The event manager state. data TimerManager -- | Retrieve the system event manager for the capability on which the -- calling thread is running. -- -- This function always returns Just the current thread's event -- manager when using the threaded RTS and Nothing otherwise. getSystemEventManager :: IO (Maybe EventManager) -- | Create a new event manager. new :: IO EventManager getSystemTimerManager :: IO TimerManager -- | An I/O event. data Event -- | Data is available to be read. evtRead :: Event -- | The file descriptor is ready to accept a write. evtWrite :: Event -- | Callback invoked on I/O events. type IOCallback = FdKey -> Event -> IO () -- | A file descriptor registration cookie. data FdKey -- | The lifetime of an event registration. data Lifetime -- | the registration will be active for only one event OneShot :: Lifetime -- | the registration will trigger multiple times MultiShot :: Lifetime -- | registerFd mgr cb fd evs lt registers interest in the events -- evs on the file descriptor fd for lifetime -- lt. cb is called for each event that occurs. Returns -- a cookie that can be handed to unregisterFd. registerFd :: EventManager -> IOCallback -> Fd -> Event -> Lifetime -> IO FdKey -- | Drop a previous file descriptor registration. unregisterFd :: EventManager -> FdKey -> IO () -- | Drop a previous file descriptor registration, without waking the event -- manager thread. The return value indicates whether the event manager -- ought to be woken. unregisterFd_ :: EventManager -> FdKey -> IO Bool -- | Close a file descriptor in a race-safe way. closeFd :: EventManager -> (Fd -> IO ()) -> Fd -> IO () -- | Callback invoked on timeout events. type TimeoutCallback = IO () -- | A timeout registration cookie. data TimeoutKey -- | Register a timeout in the given number of microseconds. The returned -- TimeoutKey can be used to later unregister or update the -- timeout. The timeout is automatically unregistered after the given -- time has passed. registerTimeout :: TimerManager -> Int -> TimeoutCallback -> IO TimeoutKey -- | Update an active timeout to fire in the given number of microseconds. updateTimeout :: TimerManager -> TimeoutKey -> Int -> IO () -- | Unregister an active timeout. unregisterTimeout :: TimerManager -> TimeoutKey -> IO () -- | Basic concurrency stuff. module GHC.Conc -- | 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. data ThreadId ThreadId :: ThreadId# -> ThreadId -- | Creates a new thread to run the IO computation passed as the -- first argument, and returns the ThreadId of the newly created -- thread. -- -- The new thread will be a lightweight, unbound thread. Foreign -- calls made by this thread are not guaranteed to be made by any -- particular OS thread; if you need foreign calls to be made by a -- particular OS thread, then use forkOS instead. -- -- The new thread inherits the masked state of the parent (see -- mask). -- -- The newly created thread has an exception handler that discards the -- exceptions BlockedIndefinitelyOnMVar, -- BlockedIndefinitelyOnSTM, and ThreadKilled, and passes -- all other exceptions to the uncaught exception handler. forkIO :: 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 capability the -- thread should run. Unlike a forkIO thread, a thread created by -- forkOn will stay on the same capability for its entire lifetime -- (forkIO threads can migrate between capabilities according to -- the scheduling policy). forkOn is useful for overriding the -- scheduling policy when you know in advance how best to distribute the -- threads. -- -- The Int argument specifies a capability number (see -- getNumCapabilities). Typically capabilities correspond to -- physical processors, but the exact behaviour is -- implementation-dependent. The value passed to forkOn is -- interpreted modulo the total number of capabilities as returned by -- getNumCapabilities. -- -- GHC note: the number of capabilities is specified by the +RTS -- -N option when the program is started. Capabilities can be fixed -- to actual processor cores with +RTS -qa if the underlying -- operating system supports that, although in practice this is usually -- unnecessary (and may actually degrade performance in some cases - -- experimentation is recommended). 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 -- | 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. To -- change this value, use setNumCapabilities. getNumCapabilities :: IO Int -- | Set 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. The initial value -- is given by the +RTS -N runtime flag. -- -- This is also the number of threads that will participate in parallel -- garbage collection. It is strongly recommended that the number of -- capabilities is not set larger than the number of physical processor -- cores, and it may often be beneficial to leave one or more cores free -- to avoid contention with other processes in the machine. setNumCapabilities :: Int -> IO () -- | Returns the number of CPUs that the machine has 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). -- -- Exception delivery synchronizes between the source and target thread: -- 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. Exception delivery is also -- atomic with respect to other exceptions. Atomicity is a useful -- property to have when dealing with race conditions: e.g. 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 infixr 0 `par` pseq :: a -> b -> b infixr 0 `pseq` -- | 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 () -- | make a weak pointer to a ThreadId. It can be important to do -- this if you want to hold a reference to a ThreadId while still -- allowing the thread to receive the BlockedIndefinitely family -- of exceptions (e.g. BlockedIndefinitelyOnMVar). Holding a -- normal ThreadId reference will prevent the delivery of -- BlockedIndefinitely exceptions because the reference could be -- used as the target of throwTo at any time, which would unblock -- the thread. -- -- Holding a Weak ThreadId, on the other hand, will not prevent -- the thread from receiving BlockedIndefinitely exceptions. It -- is still possible to throw an exception to a Weak ThreadId, -- but the caller must use deRefWeak first to determine whether -- the thread still exists. mkWeakThreadId :: ThreadId -> IO (Weak ThreadId) -- | 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 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) -- | Make a StablePtr that can be passed to the C function -- hs_try_putmvar(). The RTS wants a StablePtr to the -- underlying MVar#, but a StablePtr# can only refer to -- lifted types, so we have to cheat by coercing. newStablePtrPrimMVar :: MVar () -> IO (StablePtr PrimMVar) data PrimMVar -- | 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 () -- | Returns an STM action that can be used to wait for data to read from a -- file descriptor. The second returned value is an IO action that can be -- used to deregister interest in the file descriptor. threadWaitReadSTM :: Fd -> IO (STM (), IO ()) -- | Returns an STM action that can be used to wait until data can be -- written to a file descriptor. The second returned value is an IO -- action that can be used to deregister interest in the file descriptor. threadWaitWriteSTM :: Fd -> IO (STM (), 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 () -- | Every thread has an allocation counter that tracks how much memory has -- been allocated by the thread. The counter is initialized to zero, and -- setAllocationCounter sets the current value. The allocation -- counter counts *down*, so in the absence of a call to -- setAllocationCounter its value is the negation of the number of -- bytes of memory allocated by the thread. -- -- There are two things that you can do with this counter: -- -- -- -- Allocation accounting is accurate only to about 4Kbytes. setAllocationCounter :: Int64 -> IO () -- | Return the current value of the allocation counter for the current -- thread. getAllocationCounter :: IO Int64 -- | Enables the allocation counter to be treated as a limit for the -- current thread. When the allocation limit is enabled, if the -- allocation counter counts down below zero, the thread will be sent the -- AllocationLimitExceeded asynchronous exception. When this -- happens, the counter is reinitialised (by default to 100K, but tunable -- with the +RTS -xq option) so that it can handle the exception -- and perform any necessary clean up. If it exhausts this additional -- allowance, another AllocationLimitExceeded exception is sent, -- and so forth. Like other asynchronous exceptions, the -- AllocationLimitExceeded exception is deferred while the thread -- is inside mask or an exception handler in catch. -- -- Note that memory allocation is unrelated to live memory, also -- known as heap residency. A thread can allocate a large amount -- of memory and retain anything between none and all of it. It is better -- to think of the allocation limit as a limit on CPU time, rather -- than a limit on memory. -- -- Compared to using timeouts, allocation limits don't count time spent -- blocked or in foreign calls. enableAllocationLimit :: IO () -- | Disable allocation limit processing for the current thread. disableAllocationLimit :: 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. -- -- unsafeIOToSTM :: IO a -> STM a withMVar :: MVar a -> (a -> IO b) -> IO b type Signal = CInt type HandlerFun = ForeignPtr Word8 -> IO () setHandler :: Signal -> Maybe (HandlerFun, Dynamic) -> IO (Maybe (HandlerFun, Dynamic)) runHandlers :: ForeignPtr Word8 -> Signal -> IO () ensureIOManagerIsRunning :: IO () ioManagerCapabilitiesChanged :: IO () setUncaughtExceptionHandler :: (SomeException -> IO ()) -> IO () getUncaughtExceptionHandler :: IO (SomeException -> IO ()) reportError :: SomeException -> IO () reportStackOverflow :: IO () reportHeapOverflow :: IO () -- | Quantity semaphores in which each thread may wait for an arbitrary -- "amount". module Control.Concurrent.QSemN -- | QSemN is a quantity semaphore in which the resource is aqcuired -- and released in units of one. It provides guaranteed FIFO ordering for -- satisfying blocked waitQSemN calls. -- -- The pattern -- --
--   bracket_ (waitQSemN n) (signalQSemN n) (...)
--   
-- -- is safe; it never loses any of the resource. 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 () -- | Simple quantity semaphores. module Control.Concurrent.QSem -- | QSem is a quantity semaphore in which the resource is aqcuired -- and released in units of one. It provides guaranteed FIFO ordering for -- satisfying blocked waitQSem calls. -- -- The pattern -- --
--   bracket_ waitQSem signalQSem (...)
--   
-- -- is safe; it never loses a unit of the resource. 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 () -- | Unbounded channels. -- -- The channels are implemented with MVars and therefore inherit -- all the caveats that apply to MVars (possibility of races, -- deadlocks etc). The stm (software transactional memory) library has a -- more robust implementation of channels called TChans. 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. Blocks when the channel is -- empty. Since the read end of a channel is an MVar, this -- operation inherits fairness guarantees of MVars (e.g. threads -- blocked in this operation are woken up in FIFO order). -- -- Throws BlockedIndefinitelyOnMVar when the channel is empty -- and no other thread holds a reference to the channel. 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://ghc.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://ghc.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 GHC.Classes.Eq (Control.Concurrent.Chan.Chan a) -- | A common interface to a collection of useful concurrency abstractions. module Control.Concurrent -- | 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. data ThreadId -- | Returns the ThreadId of the calling thread (GHC only). myThreadId :: IO ThreadId -- | Creates a new thread to run the IO computation passed as the -- first argument, and returns the ThreadId of the newly created -- thread. -- -- The new thread will be a lightweight, unbound thread. Foreign -- calls made by this thread are not guaranteed to be made by any -- particular OS thread; if you need foreign calls to be made by a -- particular OS thread, then use forkOS instead. -- -- The new thread inherits the masked state of the parent (see -- mask). -- -- The newly created thread has an exception handler that discards the -- exceptions BlockedIndefinitelyOnMVar, -- BlockedIndefinitelyOnSTM, and ThreadKilled, and passes -- all other exceptions to the uncaught exception handler. forkIO :: IO () -> IO ThreadId -- | Fork a thread and call the supplied function when the thread is about -- to terminate, with an exception or a returned value. The function is -- called with asynchronous exceptions masked. -- --
--   forkFinally action and_then =
--     mask $ \restore ->
--       forkIO $ try (restore action) >>= and_then
--   
-- -- This function is useful for informing the parent when a child -- terminates, for example. forkFinally :: IO a -> (Either SomeException a -> 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 -- | 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). -- -- Exception delivery synchronizes between the source and target thread: -- 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. Exception delivery is also -- atomic with respect to other exceptions. Atomicity is a useful -- property to have when dealing with race conditions: e.g. 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 capability the -- thread should run. Unlike a forkIO thread, a thread created by -- forkOn will stay on the same capability for its entire lifetime -- (forkIO threads can migrate between capabilities according to -- the scheduling policy). forkOn is useful for overriding the -- scheduling policy when you know in advance how best to distribute the -- threads. -- -- The Int argument specifies a capability number (see -- getNumCapabilities). Typically capabilities correspond to -- physical processors, but the exact behaviour is -- implementation-dependent. The value passed to forkOn is -- interpreted modulo the total number of capabilities as returned by -- getNumCapabilities. -- -- GHC note: the number of capabilities is specified by the +RTS -- -N option when the program is started. Capabilities can be fixed -- to actual processor cores with +RTS -qa if the underlying -- operating system supports that, although in practice this is usually -- unnecessary (and may actually degrade performance in some cases - -- experimentation is recommended). 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. To -- change this value, use setNumCapabilities. getNumCapabilities :: IO Int -- | Set 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. The initial value -- is given by the +RTS -N runtime flag. -- -- This is also the number of threads that will participate in parallel -- garbage collection. It is strongly recommended that the number of -- capabilities is not set larger than the number of physical processor -- cores, and it may often be beneficial to leave one or more cores free -- to avoid contention with other processes in the machine. setNumCapabilities :: Int -> IO () -- | 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 () -- | Returns an STM action that can be used to wait for data to read from a -- file descriptor. The second returned value is an IO action that can be -- used to deregister interest in the file descriptor. threadWaitReadSTM :: Fd -> IO (STM (), IO ()) -- | Returns an STM action that can be used to wait until data can be -- written to a file descriptor. The second returned value is an IO -- action that can be used to deregister interest in the file descriptor. threadWaitWriteSTM :: Fd -> IO (STM (), IO ()) -- | 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 -- | Like forkIOWithUnmask, but the child thread is a bound thread, -- as with forkOS. forkOSWithUnmask :: ((forall a. IO a -> IO a) -> 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 its main thread to be bound and makes heavy -- use of concurrency (e.g. a web server), might want to wrap its -- 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 -- | make a weak pointer to a ThreadId. It can be important to do -- this if you want to hold a reference to a ThreadId while still -- allowing the thread to receive the BlockedIndefinitely family -- of exceptions (e.g. BlockedIndefinitelyOnMVar). Holding a -- normal ThreadId reference will prevent the delivery of -- BlockedIndefinitely exceptions because the reference could be -- used as the target of throwTo at any time, which would unblock -- the thread. -- -- Holding a Weak ThreadId, on the other hand, will not prevent -- the thread from receiving BlockedIndefinitely exceptions. It -- is still possible to throw an exception to a Weak ThreadId, -- but the caller must use deRefWeak first to determine whether -- the thread still exists. mkWeakThreadId :: ThreadId -> IO (Weak 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 GHC.Classes.Eq System.Timeout.Timeout instance GHC.Show.Show System.Timeout.Timeout instance GHC.Exception.Exception System.Timeout.Timeout -- | "Scrap your boilerplate" --- Generic programming in Haskell. See -- http://www.haskell.org/haskellwiki/Research_papers/Generics#Scrap_your_boilerplate.21. -- 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 -- | Left-associative fold operation for constructor applications. -- -- The type of gfoldl is a headache, but operationally it is a -- simple generalisation of a list fold. -- -- The default definition for gfoldl is const -- id, which is suitable for abstract datatypes with no -- substructures. gfoldl :: Data a => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a -- | Unfolding constructor applications gunfold :: Data a => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a -- | Obtaining the constructor from a given datum. For proper terms, this -- is meant to be the top-level constructor. Primitive datatypes are here -- viewed as potentially infinite sets of values (i.e., constructors). toConstr :: Data a => a -> Constr -- | The outer type constructor of the type dataTypeOf :: Data a => a -> DataType -- | Mediate types and unary type constructors. In Data instances of -- the form T a, dataCast1 should be defined as -- gcast1. -- -- The default definition is const Nothing, which -- is appropriate for non-unary type constructors. dataCast1 :: (Data a, Typeable t) => (forall d. Data d => c (t d)) -> Maybe (c a) -- | Mediate types and binary type constructors. In Data instances -- of the form T a b, dataCast2 should be defined as -- gcast2. -- -- The default definition is const Nothing, which -- is appropriate for non-binary type constructors. dataCast2 :: (Data a, Typeable t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a) -- | A generic transformation that maps over the immediate subterms -- -- The default definition instantiates the type constructor c in -- the type of gfoldl to an identity datatype constructor, using -- the isomorphism pair as injection and projection. gmapT :: Data a => (forall b. Data b => b -> b) -> a -> a -- | A generic query with a left-associative binary operator gmapQl :: forall r r'. Data a => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r -- | A generic query with a right-associative binary operator gmapQr :: forall r r'. Data a => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r -- | A generic query that processes the immediate subterms and returns a -- list of results. The list is given in the same order as originally -- specified in the declaration of the data constructors. gmapQ :: Data a => (forall d. Data d => d -> u) -> a -> [u] -- | A generic query that processes one child by index (zero-based) gmapQi :: forall u. Data a => Int -> (forall d. Data d => d -> u) -> a -> u -- | A generic monadic transformation that maps over the immediate subterms -- -- The default definition instantiates the type constructor c in -- the type of gfoldl to the monad datatype constructor, defining -- injection and projection using return and >>=. gmapM :: forall m. (Data a, Monad m) => (forall d. Data d => d -> m d) -> a -> m a -- | Transformation of at least one immediate subterm does not fail gmapMp :: forall m. (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Transformation of one immediate subterm with success gmapMo :: forall m. (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 -- | Constructs the Char type mkCharType :: String -> DataType -- | Constructs a non-representation for a non-representable type 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 mkIntegralConstr :: (Integral a, Show a) => DataType -> a -> Constr mkRealConstr :: (Real a, Show a) => DataType -> a -> 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 :: forall m a. (Monad m, Data a) => (forall d. Data d => m d) -> Constr -> m a instance GHC.Show.Show Data.Data.DataRep instance GHC.Classes.Eq Data.Data.DataRep instance GHC.Show.Show Data.Data.DataType instance GHC.Show.Show Data.Data.Fixity instance GHC.Classes.Eq Data.Data.Fixity instance GHC.Show.Show Data.Data.ConstrRep instance GHC.Classes.Eq Data.Data.ConstrRep instance Data.Data.Data GHC.Types.Bool instance Data.Data.Data a => Data.Data.Data (GHC.Base.Maybe a) instance Data.Data.Data GHC.Types.Ordering instance (Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Data.Either.Either a b) instance Data.Data.Data () instance (Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (a, b) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c) => Data.Data.Data (a, b, c) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c, Data.Data.Data d) => Data.Data.Data (a, b, c, d) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c, Data.Data.Data d, Data.Data.Data e) => Data.Data.Data (a, b, c, d, e) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c, Data.Data.Data d, Data.Data.Data e, Data.Data.Data f) => Data.Data.Data (a, b, c, d, e, f) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c, Data.Data.Data d, Data.Data.Data e, Data.Data.Data f, Data.Data.Data g) => Data.Data.Data (a, b, c, d, e, f, g) instance Data.Data.Data t => Data.Data.Data (Data.Proxy.Proxy t) instance (a ~ b, Data.Data.Data a) => Data.Data.Data (a Data.Type.Equality.:~: b) instance forall k1 k2 (i1 :: k2) (j1 :: k1) i2 j2 (a :: i2) (b :: j2). (Data.Typeable.Internal.Typeable i2, Data.Typeable.Internal.Typeable j2, Data.Typeable.Internal.Typeable a, Data.Typeable.Internal.Typeable b, (a :: i2) ~~ (b :: j2)) => Data.Data.Data (a Data.Type.Equality.:~~: b) instance (GHC.Types.Coercible a b, Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Data.Type.Coercion.Coercion a b) instance Data.Data.Data a => Data.Data.Data (Data.Functor.Identity.Identity a) instance forall k1 (k2 :: k1) k3 a (b :: k3). (Data.Typeable.Internal.Typeable k3, Data.Data.Data a, Data.Typeable.Internal.Typeable b) => Data.Data.Data (Data.Functor.Const.Const a b) instance Data.Data.Data Data.Version.Version instance Data.Data.Data a => Data.Data.Data (Data.Monoid.Dual a) instance Data.Data.Data Data.Monoid.All instance Data.Data.Data Data.Monoid.Any instance Data.Data.Data a => Data.Data.Data (Data.Monoid.Sum a) instance Data.Data.Data a => Data.Data.Data (Data.Monoid.Product a) instance Data.Data.Data a => Data.Data.Data (Data.Monoid.First a) instance Data.Data.Data a => Data.Data.Data (Data.Monoid.Last a) instance (Data.Data.Data (f a), Data.Data.Data a, Data.Typeable.Internal.Typeable f) => Data.Data.Data (Data.Monoid.Alt f a) instance Data.Data.Data p => Data.Data.Data (GHC.Generics.U1 p) instance Data.Data.Data p => Data.Data.Data (GHC.Generics.Par1 p) instance (Data.Data.Data (f p), Data.Typeable.Internal.Typeable f, Data.Data.Data p) => Data.Data.Data (GHC.Generics.Rec1 f p) instance (Data.Typeable.Internal.Typeable i, Data.Data.Data p, Data.Data.Data c) => Data.Data.Data (GHC.Generics.K1 i c p) instance (Data.Data.Data p, Data.Data.Data (f p), Data.Typeable.Internal.Typeable c, Data.Typeable.Internal.Typeable i, Data.Typeable.Internal.Typeable f) => Data.Data.Data (GHC.Generics.M1 i c f p) instance (Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable g, Data.Data.Data p, Data.Data.Data (f p), Data.Data.Data (g p)) => Data.Data.Data ((GHC.Generics.:+:) f g p) instance (Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable g, Data.Data.Data p, Data.Data.Data (f (g p))) => Data.Data.Data ((GHC.Generics.:.:) f g p) instance Data.Data.Data p => Data.Data.Data (GHC.Generics.V1 p) instance (Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable g, Data.Data.Data p, Data.Data.Data (f p), Data.Data.Data (g p)) => Data.Data.Data ((GHC.Generics.:*:) f g p) instance Data.Data.Data GHC.Generics.Fixity instance Data.Data.Data GHC.Generics.Associativity instance Data.Data.Data GHC.Generics.SourceUnpackedness instance Data.Data.Data GHC.Generics.SourceStrictness instance Data.Data.Data GHC.Generics.DecidedStrictness instance Data.Data.Data GHC.Types.Char instance Data.Data.Data GHC.Types.Float instance Data.Data.Data GHC.Types.Double instance Data.Data.Data GHC.Types.Int instance Data.Data.Data GHC.Integer.Type.Integer instance Data.Data.Data GHC.Natural.Natural instance Data.Data.Data GHC.Int.Int8 instance Data.Data.Data GHC.Int.Int16 instance Data.Data.Data GHC.Int.Int32 instance Data.Data.Data GHC.Int.Int64 instance Data.Data.Data GHC.Types.Word instance Data.Data.Data GHC.Word.Word8 instance Data.Data.Data GHC.Word.Word16 instance Data.Data.Data GHC.Word.Word32 instance Data.Data.Data GHC.Word.Word64 instance (Data.Data.Data a, GHC.Real.Integral a) => Data.Data.Data (GHC.Real.Ratio a) instance Data.Data.Data a => Data.Data.Data [a] instance Data.Data.Data a => Data.Data.Data (GHC.Ptr.Ptr a) instance Data.Data.Data a => Data.Data.Data (GHC.ForeignPtr.ForeignPtr a) instance (Data.Data.Data a, Data.Data.Data b, GHC.Arr.Ix a) => Data.Data.Data (GHC.Arr.Array a b) instance GHC.Show.Show Data.Data.Constr instance GHC.Classes.Eq Data.Data.Constr -- | GHC Extensions: this is the Approved Way to get at GHC-specific -- extensions. -- -- Note: no other base module should import this module. 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 -- -- -- -- A value of type FunPtr a may be a pointer to a foreign -- function, either returned by another foreign function or imported with -- a a static address import like -- --
--   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). The RL means "right, logical" (as opposed to -- RA for arithmetic) (although an arithmetic right shift wouldn't make -- sense for Word#) 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). The RA means "right, arithmetic" -- (as opposed to RL for logical) iShiftRA# :: Int# -> Int# -> Int# -- | Shift the argument right (unsigned) by the specified number of bits -- (which must be non-negative). The RL means "right, logical" (as -- opposed to RA for arithmetic) iShiftRL# :: Int# -> Int# -> Int# uncheckedShiftL64# :: Word# -> Int# -> Word# uncheckedShiftRL64# :: Word# -> Int# -> Word# uncheckedIShiftL64# :: Int# -> Int# -> Int# uncheckedIShiftRA64# :: Int# -> Int# -> Int# -- | Alias for tagToEnum#. Returns True if its parameter is 1# and -- False if it is 0#. isTrue# :: Int# -> Bool -- | 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 a. (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 a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] -- | Class for string-like datastructures; used by the overloaded string -- extension (-XOverloadedStrings in GHC). class IsString a fromString :: IsString a => String -> a breakpoint :: a -> a breakpointCond :: Bool -> a -> a -- | The lazy function restrains strictness analysis a little. The -- call lazy e means the same as e, but lazy has -- a magical property so far as strictness analysis is concerned: it is -- lazy in its first argument, even though its semantics is strict. After -- strictness analysis has run, calls to lazy are inlined to be -- the identity function. -- -- This behaviour is occasionally useful when controlling evaluation -- order. Notably, lazy is used in the library definition of -- par: -- --
--   par :: a -> b -> b
--   par x y = case (par# x) of _ -> lazy y
--   
-- -- If lazy were not lazy, par would look strict in -- y which would defeat the whole purpose of par. -- -- Like seq, the argument of lazy can have an unboxed type. lazy :: () => a -> a -- | The call inline f arranges that f is inlined, -- regardless of its size. More precisely, the call inline f -- rewrites to the right-hand side of f's definition. This -- allows the programmer to control inlining from a particular call site -- rather than the definition site of the function (c.f. INLINE -- pragmas). -- -- This inlining occurs regardless of the argument to the call or the -- size of f's definition; it is unconditional. The main caveat -- is that f's definition must be visible to the compiler; it is -- therefore recommended to mark the function with an INLINABLE -- pragma at its definition so that GHC guarantees to record its -- unfolding regardless of size. -- -- If no inlining takes place, the inline function expands to the -- identity function in Phase zero, so its use imposes no overhead. inline :: () => a -> a -- | The oneShot function can be used to give a hint to the compiler -- that its argument will be called at most once, which may (or may not) -- enable certain optimizations. It can be useful to improve the -- performance of code in continuation passing style. -- -- If oneShot is used wrongly, then it may be that computations -- whose result that would otherwise be shared are re-evaluated every -- time they are used. Otherwise, the use of oneShot is safe. -- -- oneShot is representation polymorphic: the type variables may -- refer to lifted or unlifted types. oneShot :: () => (a -> b) -> a -> b -- | Apply a function to a 'State# RealWorld' token. When manually applying -- a function to realWorld#, it is necessary to use -- NOINLINE to prevent semantically undesirable floating. -- runRW# is inlined, but only very late in compilation after all -- floating is complete. runRW# :: () => (State# RealWorld -> a) -> a -- | The function coerce allows you to safely convert between -- values of types that have the same representation with no run-time -- overhead. In the simplest case you can use it instead of a newtype -- constructor, to go from the newtype's concrete type to the abstract -- type. But it also works in more complicated settings, e.g. converting -- a list of newtypes to a list of concrete types. coerce :: Coercible * a b => a -> b -- | Coercible is a two-parameter class that has instances for -- types a and b if the compiler can infer that they -- have the same representation. This class does not have regular -- instances; instead they are created on-the-fly during type-checking. -- Trying to manually declare an instance of Coercible is an -- error. -- -- Nevertheless one can pretend that the following three kinds of -- instances exist. First, as a trivial base-case: -- --
--   instance Coercible a a
--   
-- -- Furthermore, for every type constructor there is an instance that -- allows to coerce under the type constructor. For example, let -- D be a prototypical type constructor (data or -- newtype) with three type arguments, which have roles -- nominal, representational resp. phantom. -- Then there is an instance of the form -- --
--   instance Coercible b b' => Coercible (D a b c) (D a b' c')
--   
-- -- Note that the nominal type arguments are equal, the -- representational type arguments can differ, but need to have -- a Coercible instance themself, and the phantom type -- arguments can be changed arbitrarily. -- -- The third kind of instance exists for every newtype NT = MkNT -- T and comes in two variants, namely -- --
--   instance Coercible a T => Coercible a NT
--   
-- --
--   instance Coercible T b => Coercible NT b
--   
-- -- This instance is only usable if the constructor MkNT is in -- scope. -- -- If, as a library author of a type constructor like Set a, you -- want to prevent a user of your module to write coerce :: Set T -- -> Set NT, you need to set the role of Set's type -- parameter to nominal, by writing -- --
--   type role Set nominal
--   
-- -- For more details about this feature, please refer to Safe -- Coercions by Joachim Breitner, Richard A. Eisenberg, Simon Peyton -- Jones and Stephanie Weirich. class (~R#) k0 k0 a b => Coercible k0 (a :: k0) (b :: k0) -- | Lifted, heterogeneous equality. By lifted, we mean that it can be -- bogus (deferred type error). By heterogeneous, the two types -- a and b might have different kinds. Because -- ~~ can appear unexpectedly in error messages to users who do -- not care about the difference between heterogeneous equality -- ~~ and homogeneous equality ~, this is printed as -- ~ unless -fprint-equality-relations is set. class (~#) k0 k1 a b => (~~) k0 k1 (a :: k0) (b :: k1) data TYPE (a :: RuntimeRep) :: RuntimeRep -> * -- | GHC maintains a property that the kind of all inhabited types (as -- distinct from type constructors or type-level data) tells us the -- runtime representation of values of that type. This datatype encodes -- the choice of runtime value. Note that TYPE is parameterised by -- RuntimeRep; this is precisely what we mean by the fact that a -- type's kind encodes the runtime representation. -- -- For boxed values (that is, values that are represented by a pointer), -- a further distinction is made, between lifted types (that contain ⊥), -- and unlifted ones (that don't). data RuntimeRep :: * -- | a SIMD vector type VecRep :: VecCount -> VecElem -> RuntimeRep -- | An unboxed tuple of the given reps TupleRep :: [RuntimeRep] -> RuntimeRep -- | An unboxed sum of the given reps SumRep :: [RuntimeRep] -> RuntimeRep -- | lifted; represented by a pointer LiftedRep :: RuntimeRep -- | unlifted; represented by a pointer UnliftedRep :: RuntimeRep -- | signed, word-sized value IntRep :: RuntimeRep -- | unsigned, word-sized value WordRep :: RuntimeRep -- | signed, 64-bit value (on 32-bit only) Int64Rep :: RuntimeRep -- | unsigned, 64-bit value (on 32-bit only) Word64Rep :: RuntimeRep -- | A pointer, but not to a Haskell value AddrRep :: RuntimeRep -- | a 32-bit floating point number FloatRep :: RuntimeRep -- | a 64-bit floating point number DoubleRep :: RuntimeRep -- | Length of a SIMD vector type data VecCount :: * Vec2 :: VecCount Vec4 :: VecCount Vec8 :: VecCount Vec16 :: VecCount Vec32 :: VecCount Vec64 :: VecCount -- | Element of a SIMD vector type data VecElem :: * Int8ElemRep :: VecElem Int16ElemRep :: VecElem Int32ElemRep :: VecElem Int64ElemRep :: VecElem Word8ElemRep :: VecElem Word16ElemRep :: VecElem Word32ElemRep :: VecElem Word64ElemRep :: VecElem FloatElemRep :: VecElem DoubleElemRep :: VecElem -- | 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 -- -- Provides Show and Read instances (since: -- 4.7.0.0). 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 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 traceEvent or 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 maintained 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] -- | The kind of constraints, like Show a data Constraint :: * -- | The type constructor Any is type to which you can unsafely -- coerce any lifted type, and back. More concretely, for a lifted type -- t and value x :: t, -- unsafeCoerce -- (unsafeCoerce x :: Any) :: t is equivalent to x. -- | The IsList class and its methods are intended to be used in -- conjunction with the OverloadedLists extension. class IsList l where { type family Item l; } -- | The fromList function constructs the structure l from -- the given list of Item l fromList :: IsList l => [Item l] -> l -- | The fromListN function takes the input list's length as a hint. -- Its behaviour should be equivalent to fromList. The hint can be -- used to construct the structure l more efficiently compared -- to fromList. If the given hint does not equal to the input -- list's length the behaviour of fromListN is not specified. fromListN :: IsList l => Int -> [Item l] -> l -- | The toList function extracts a list of Item l from the -- structure l. It should satisfy fromList . toList = id. toList :: IsList l => l -> [Item l] instance GHC.Classes.Eq GHC.Exts.SpecConstrAnnotation instance Data.Data.Data GHC.Exts.SpecConstrAnnotation instance GHC.Exts.IsList [a] instance GHC.Exts.IsList Data.Version.Version instance GHC.Exts.IsList GHC.Stack.Types.CallStack -- | Symbolic references to values. -- -- References to values are usually implemented with memory addresses, -- and this is practical when communicating values between the different -- pieces of a single process. -- -- When values are communicated across different processes running in -- possibly different machines, though, addresses are no longer useful -- since each process may use different addresses to store a given value. -- -- To solve such concern, the references provided by this module offer a -- key that can be used to locate the values on each process. Each -- process maintains a global table of references which can be looked up -- with a given key. This table is known as the Static Pointer Table. The -- reference can then be dereferenced to obtain the value. module GHC.StaticPtr -- | A reference to a value of type a. data StaticPtr a -- | Dereferences a static pointer. deRefStaticPtr :: StaticPtr a -> a -- | A key for StaticPtrs that can be serialized and used with -- unsafeLookupStaticPtr. type StaticKey = Fingerprint -- | The StaticKey that can be used to look up the given -- StaticPtr. staticKey :: StaticPtr a -> StaticKey -- | Looks up a StaticPtr by its StaticKey. -- -- If the StaticPtr is not found returns Nothing. -- -- This function is unsafe because the program behavior is undefined if -- the type of the returned StaticPtr does not match the expected -- one. unsafeLookupStaticPtr :: StaticKey -> IO (Maybe (StaticPtr a)) -- | Miscelaneous information available for debugging purposes. data StaticPtrInfo StaticPtrInfo :: String -> String -> (Int, Int) -> StaticPtrInfo -- | Package key of the package where the static pointer is defined [spInfoUnitId] :: StaticPtrInfo -> String -- | Name of the module where the static pointer is defined [spInfoModuleName] :: StaticPtrInfo -> String -- | Source location of the definition of the static pointer as a -- (Line, Column) pair. [spInfoSrcLoc] :: StaticPtrInfo -> (Int, Int) -- | StaticPtrInfo of the given StaticPtr. staticPtrInfo :: StaticPtr a -> StaticPtrInfo -- | A list of all known keys. staticPtrKeys :: IO [StaticKey] -- | A class for things buildable from static pointers. class IsStatic p fromStaticPtr :: IsStatic p => StaticPtr a -> p a instance GHC.Show.Show GHC.StaticPtr.StaticPtrInfo instance GHC.StaticPtr.IsStatic GHC.StaticPtr.StaticPtr -- | A logically uninhabited data type, used to indicate that a given term -- should not exist. module Data.Void -- | Uninhabited data type data Void -- | Since Void values logically don't exist, this witnesses the -- logical reasoning tool of "ex falso quodlibet". absurd :: Void -> a -- | If Void is uninhabited then any Functor that holds only -- values of type Void is holding no values. vacuous :: Functor f => f Void -> f a instance GHC.Generics.Generic Data.Void.Void instance Data.Data.Data Data.Void.Void instance GHC.Classes.Eq Data.Void.Void instance GHC.Classes.Ord Data.Void.Void instance GHC.Read.Read Data.Void.Void instance GHC.Show.Show Data.Void.Void instance GHC.Arr.Ix Data.Void.Void instance GHC.Exception.Exception Data.Void.Void -- | A NonEmpty list is one which always has at least one element, -- but is otherwise identical to the traditional list type in complexity -- and in terms of API. You will almost certainly want to import this -- module qualified. module Data.List.NonEmpty -- | Non-empty (and non-strict) list type. data NonEmpty a (:|) :: a -> [a] -> NonEmpty a -- | Map a function over a NonEmpty stream. map :: (a -> b) -> NonEmpty a -> NonEmpty b -- | 'intersperse x xs' alternates elements of the list with copies of -- x. -- --
--   intersperse 0 (1 :| [2,3]) == 1 :| [0,2,0,3]
--   
intersperse :: a -> NonEmpty a -> NonEmpty a -- | scanl is similar to foldl, but returns a stream 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 :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b -- | scanr is the right-to-left dual of scanl. Note that -- --
--   head (scanr f z xs) == foldr f z xs.
--   
scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
--   scanl1 f [x1, x2, ...] == x1 :| [x1 `f` x2, x1 `f` (x2 `f` x3), ...]
--   
scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a -- | transpose for NonEmpty, behaves the same as -- transpose The rows/columns need not be the same length, in -- which case > transpose . transpose /= id transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a) -- | sortBy for NonEmpty, behaves the same as sortBy sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a -- | sortWith for NonEmpty, behaves the same as: -- --
--   sortBy . comparing
--   
sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a -- | Number of elements in NonEmpty list. length :: NonEmpty a -> Int -- | Extract the first element of the stream. head :: NonEmpty a -> a -- | Extract the possibly-empty tail of the stream. tail :: NonEmpty a -> [a] -- | Extract the last element of the stream. last :: NonEmpty a -> a -- | Extract everything except the last element of the stream. init :: NonEmpty a -> [a] -- | Prepend an element to the stream. (<|) :: a -> NonEmpty a -> NonEmpty a infixr 5 <| -- | Synonym for <|. cons :: a -> NonEmpty a -> NonEmpty a -- | uncons produces the first element of the stream, and a stream -- of the remaining elements, if any. uncons :: NonEmpty a -> (a, Maybe (NonEmpty a)) -- | The unfoldr function is analogous to Data.List's -- unfoldr operation. unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b -- | Sort a stream. sort :: Ord a => NonEmpty a -> NonEmpty a -- | reverse a finite NonEmpty stream. reverse :: NonEmpty a -> NonEmpty a -- | The inits function takes a stream xs and returns all -- the finite prefixes of xs. inits :: Foldable f => f a -> NonEmpty [a] -- | The tails function takes a stream xs and returns all -- the suffixes of xs. tails :: Foldable f => f a -> NonEmpty [a] -- | iterate f x produces the infinite sequence of repeated -- applications of f to x. -- --
--   iterate f x = x :| [f x, f (f x), ..]
--   
iterate :: (a -> a) -> a -> NonEmpty a -- | repeat x returns a constant stream, where all elements -- are equal to x. repeat :: a -> NonEmpty a -- | cycle xs returns the infinite repetition of -- xs: -- --
--   cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...]
--   
cycle :: NonEmpty a -> NonEmpty a -- | unfold produces a new stream by repeatedly applying the -- unfolding function to the seed value to produce an element of type -- b and a new seed value. When the unfolding function returns -- Nothing instead of a new seed value, the stream ends. -- | Deprecated: Use unfoldr unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b -- | insert x xs inserts x into the last position -- in xs where it is still less than or equal to the next -- element. In particular, if the list is sorted beforehand, the result -- will also be sorted. insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a -- | some1 x sequences x one or more times. some1 :: Alternative f => f a -> f (NonEmpty a) -- | take n xs returns the first n elements of -- xs. take :: Int -> NonEmpty a -> [a] -- | drop n xs drops the first n elements off the -- front of the sequence xs. drop :: Int -> NonEmpty a -> [a] -- | splitAt n xs returns a pair consisting of the prefix -- of xs of length n and the remaining stream -- immediately following this prefix. -- --
--   'splitAt' n xs == ('take' n xs, 'drop' n xs)
--   xs == ys ++ zs where (ys, zs) = 'splitAt' n xs
--   
splitAt :: Int -> NonEmpty a -> ([a], [a]) -- | takeWhile p xs returns the longest prefix of the -- stream xs for which the predicate p holds. takeWhile :: (a -> Bool) -> NonEmpty a -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. dropWhile :: (a -> Bool) -> NonEmpty a -> [a] -- | span p xs returns the longest prefix of xs -- that satisfies p, together with the remainder of the stream. -- --
--   'span' p xs == ('takeWhile' p xs, 'dropWhile' p xs)
--   xs == ys ++ zs where (ys, zs) = 'span' p xs
--   
span :: (a -> Bool) -> NonEmpty a -> ([a], [a]) -- | The break p function is equivalent to span -- (not . p). break :: (a -> Bool) -> NonEmpty a -> ([a], [a]) -- | filter p xs removes any elements from xs that -- do not satisfy p. filter :: (a -> Bool) -> NonEmpty a -> [a] -- | The partition function takes a predicate p and a -- stream xs, and returns a pair of lists. The first list -- corresponds to the elements of xs for which p holds; -- the second corresponds to the elements of xs for which -- p does not hold. -- --
--   'partition' p xs = ('filter' p xs, 'filter' (not . p) xs)
--   
partition :: (a -> Bool) -> NonEmpty a -> ([a], [a]) -- | The group function takes a stream and returns a list of streams -- such that flattening the resulting list is equal to the argument. -- Moreover, each stream in the resulting list contains only equal -- elements. For example, in list notation: -- --
--   'group' $ 'cycle' "Mississippi"
--     = "M" : "i" : "ss" : "i" : "ss" : "i" : "pp" : "i" : "M" : "i" : ...
--   
group :: (Foldable f, Eq a) => f a -> [NonEmpty a] -- | groupBy operates like group, but uses the provided -- equality predicate instead of ==. groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a] -- | groupWith operates like group, but uses the provided -- projection when comparing for equality groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a] -- | groupAllWith operates like groupWith, but sorts the list -- first so that each equivalence class has, at most, one list in the -- output groupAllWith :: (Ord b) => (a -> b) -> [a] -> [NonEmpty a] -- | group1 operates like group, but uses the knowledge that -- its input is non-empty to produce guaranteed non-empty output. group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a) -- | groupBy1 is to group1 as groupBy is to -- group. groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a) -- | groupWith1 is to group1 as groupWith is to -- group groupWith1 :: (Eq b) => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) -- | groupAllWith1 is to groupWith1 as groupAllWith is -- to groupWith groupAllWith1 :: (Ord b) => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) -- | The isPrefix function returns True if the first -- argument is a prefix of the second. isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool -- | 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 -- inequality test. nub :: Eq a => NonEmpty a -> NonEmpty 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) -> NonEmpty a -> NonEmpty a -- | xs !! n returns the element of the stream xs at -- index n. Note that the head of the stream has index 0. -- -- Beware: a negative or out-of-bounds index will cause an error. (!!) :: NonEmpty a -> Int -> a -- | The zip function takes two streams and returns a stream of -- corresponding pairs. zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) -- | The zipWith function generalizes zip. Rather than -- tupling the elements, the elements are combined using the function -- passed as the first argument. zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c -- | The unzip function is the inverse of the zip function. unzip :: Functor f => f (a, b) -> (f a, f b) -- | Converts a normal list to a NonEmpty stream. -- -- Raises an error if given an empty list. fromList :: [a] -> NonEmpty a -- | Convert a stream to a normal list efficiently. toList :: NonEmpty a -> [a] -- | nonEmpty efficiently turns a normal list into a NonEmpty -- stream, producing Nothing if the input is empty. nonEmpty :: [a] -> Maybe (NonEmpty a) -- | Compute n-ary logic exclusive OR operation on NonEmpty list. xor :: NonEmpty Bool -> Bool instance GHC.Generics.Generic1 Data.List.NonEmpty.NonEmpty instance GHC.Generics.Generic (Data.List.NonEmpty.NonEmpty a) instance Data.Data.Data a => Data.Data.Data (Data.List.NonEmpty.NonEmpty a) instance GHC.Read.Read a => GHC.Read.Read (Data.List.NonEmpty.NonEmpty a) instance GHC.Show.Show a => GHC.Show.Show (Data.List.NonEmpty.NonEmpty a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.List.NonEmpty.NonEmpty a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.List.NonEmpty.NonEmpty a) instance Data.Functor.Classes.Eq1 Data.List.NonEmpty.NonEmpty instance Data.Functor.Classes.Ord1 Data.List.NonEmpty.NonEmpty instance Data.Functor.Classes.Read1 Data.List.NonEmpty.NonEmpty instance Data.Functor.Classes.Show1 Data.List.NonEmpty.NonEmpty instance GHC.Exts.IsList (Data.List.NonEmpty.NonEmpty a) instance Control.Monad.Fix.MonadFix Data.List.NonEmpty.NonEmpty instance Control.Monad.Zip.MonadZip Data.List.NonEmpty.NonEmpty instance GHC.Base.Functor Data.List.NonEmpty.NonEmpty instance GHC.Base.Applicative Data.List.NonEmpty.NonEmpty instance GHC.Base.Monad Data.List.NonEmpty.NonEmpty instance Data.Traversable.Traversable Data.List.NonEmpty.NonEmpty instance Data.Foldable.Foldable Data.List.NonEmpty.NonEmpty -- | In mathematics, a semigroup is an algebraic structure consisting of a -- set together with an associative binary operation. A semigroup -- generalizes a monoid in that there might not exist an identity -- element. It also (originally) generalized a group (a monoid with all -- inverses) to a type where every element did not have to have an -- inverse, thus the name semigroup. -- -- The use of (<>) in this module conflicts with an -- operator with the same name that is being exported by Data.Monoid. -- However, this package re-exports (most of) the contents of -- Data.Monoid, so to use semigroups and monoids in the same package just -- --
--   import Data.Semigroup
--   
module Data.Semigroup -- | The class of semigroups (types with an associative binary operation). class Semigroup a -- | An associative operation. -- --
--   (a <> b) <> c = a <> (b <> c)
--   
-- -- If a is also a Monoid we further require -- --
--   (<>) = mappend
--   
(<>) :: Semigroup a => a -> a -> a -- | An associative operation. -- --
--   (a <> b) <> c = a <> (b <> c)
--   
-- -- If a is also a Monoid we further require -- --
--   (<>) = mappend
--   
(<>) :: (Semigroup a, Monoid a) => a -> a -> a -- | Reduce a non-empty list with <> -- -- The default definition should be sufficient, but this can be -- overridden for efficiency. sconcat :: Semigroup a => NonEmpty a -> a -- | Repeat a value n times. -- -- Given that this works on a Semigroup it is allowed to fail if -- you request 0 or fewer repetitions, and the default definition will do -- so. -- -- By making this a member of the class, idempotent semigroups and -- monoids can upgrade this to execute in O(1) by picking -- stimes = stimesIdempotent or stimes = -- stimesIdempotentMonoid respectively. stimes :: (Semigroup a, Integral b) => b -> a -> a -- | This is a valid definition of stimes for a Monoid. -- -- Unlike the default definition of stimes, it is defined for 0 -- and so it should be preferred where possible. stimesMonoid :: (Integral b, Monoid a) => b -> a -> a -- | This is a valid definition of stimes for an idempotent -- Semigroup. -- -- When x <> x = x, this definition should be preferred, -- because it works in O(1) rather than O(log n). stimesIdempotent :: Integral b => b -> a -> a -- | This is a valid definition of stimes for an idempotent -- Monoid. -- -- When mappend x x = x, this definition should be preferred, -- because it works in O(1) rather than O(log n) stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a -- | Repeat a value n times. -- --
--   mtimesDefault n a = a <> a <> ... <> a  -- using <> (n-1) times
--   
-- -- Implemented using stimes and mempty. -- -- This is a suitable definition for an mtimes member of -- Monoid. mtimesDefault :: (Integral b, Monoid a) => b -> a -> a newtype Min a Min :: a -> Min a [getMin] :: Min a -> a newtype Max a Max :: a -> Max a [getMax] :: Max a -> a -- | Use Option (First a) to get the behavior of -- First from Data.Monoid. newtype First a First :: a -> First a [getFirst] :: First a -> a -- | Use Option (Last a) to get the behavior of -- Last from Data.Monoid newtype Last a Last :: a -> Last a [getLast] :: Last a -> a -- | Provide a Semigroup for an arbitrary Monoid. newtype WrappedMonoid m WrapMonoid :: m -> WrappedMonoid m [unwrapMonoid] :: WrappedMonoid m -> m -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following laws: -- -- -- -- The method names refer to the monoid of lists under concatenation, but -- there are many other instances. -- -- Some types can be viewed as a monoid in more than one way, e.g. both -- addition and multiplication on numbers. In such cases we often define -- newtypes and make those instances of Monoid, e.g. -- Sum and Product. class Monoid a -- | Identity of mappend mempty :: Monoid a => a -- | An associative operation mappend :: Monoid a => a -> a -> a -- | Fold a list using the monoid. For most types, the default definition -- for mconcat will be used, but the function is included in the -- class definition so that an optimized version can be provided for -- specific types. mconcat :: Monoid a => [a] -> a -- | The dual of a Monoid, obtained by swapping the arguments of -- mappend. newtype Dual a Dual :: a -> Dual a [getDual] :: Dual a -> a -- | The monoid of endomorphisms under composition. newtype Endo a Endo :: (a -> a) -> Endo a [appEndo] :: Endo a -> a -> a -- | Boolean monoid under conjunction (&&). newtype All All :: Bool -> All [getAll] :: All -> Bool -- | Boolean monoid under disjunction (||). newtype Any Any :: Bool -> Any [getAny] :: Any -> Bool -- | Monoid under addition. newtype Sum a Sum :: a -> Sum a [getSum] :: Sum a -> a -- | Monoid under multiplication. newtype Product a Product :: a -> Product a [getProduct] :: Product a -> a -- | Option is effectively Maybe with a better instance of -- Monoid, built off of an underlying Semigroup instead of -- an underlying Monoid. -- -- Ideally, this type would not exist at all and we would just fix the -- Monoid instance of Maybe newtype Option a Option :: Maybe a -> Option a [getOption] :: Option a -> Maybe a -- | Fold an Option case-wise, just like maybe. option :: b -> (a -> b) -> Option a -> b -- | This lets you use a difference list of a Semigroup as a -- Monoid. diff :: Semigroup m => m -> Endo m -- | A generalization of cycle to an arbitrary Semigroup. May -- fail to terminate for some values in some semigroups. cycle1 :: Semigroup m => m -> m -- | Arg isn't itself a Semigroup in its own right, but it -- can be placed inside Min and Max to compute an arg min -- or arg max. data Arg a b Arg :: a -> b -> Arg a b type ArgMin a b = Min (Arg a b) type ArgMax a b = Max (Arg a b) instance GHC.Generics.Generic1 Data.Semigroup.Option instance GHC.Generics.Generic (Data.Semigroup.Option a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Option a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Option a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Option a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Option a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Option a) instance GHC.Generics.Generic1 Data.Semigroup.WrappedMonoid instance GHC.Generics.Generic (Data.Semigroup.WrappedMonoid m) instance Data.Data.Data m => Data.Data.Data (Data.Semigroup.WrappedMonoid m) instance GHC.Read.Read m => GHC.Read.Read (Data.Semigroup.WrappedMonoid m) instance GHC.Show.Show m => GHC.Show.Show (Data.Semigroup.WrappedMonoid m) instance GHC.Classes.Ord m => GHC.Classes.Ord (Data.Semigroup.WrappedMonoid m) instance GHC.Classes.Eq m => GHC.Classes.Eq (Data.Semigroup.WrappedMonoid m) instance GHC.Enum.Bounded m => GHC.Enum.Bounded (Data.Semigroup.WrappedMonoid m) instance GHC.Generics.Generic1 Data.Semigroup.Last instance GHC.Generics.Generic (Data.Semigroup.Last a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Last a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Last a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Last a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Last a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Last a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.Last a) instance GHC.Generics.Generic1 Data.Semigroup.First instance GHC.Generics.Generic (Data.Semigroup.First a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.First a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.First a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.First a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.First a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.First a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.First a) instance GHC.Generics.Generic1 (Data.Semigroup.Arg a) instance GHC.Generics.Generic (Data.Semigroup.Arg a b) instance (Data.Data.Data b, Data.Data.Data a) => Data.Data.Data (Data.Semigroup.Arg a b) instance (GHC.Read.Read b, GHC.Read.Read a) => GHC.Read.Read (Data.Semigroup.Arg a b) instance (GHC.Show.Show b, GHC.Show.Show a) => GHC.Show.Show (Data.Semigroup.Arg a b) instance GHC.Generics.Generic1 Data.Semigroup.Max instance GHC.Generics.Generic (Data.Semigroup.Max a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Max a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Max a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Max a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Max a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Max a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.Max a) instance GHC.Generics.Generic1 Data.Semigroup.Min instance GHC.Generics.Generic (Data.Semigroup.Min a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Min a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Min a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Min a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Min a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Min a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.Min a) instance GHC.Base.Functor Data.Semigroup.Option instance GHC.Base.Applicative Data.Semigroup.Option instance GHC.Base.Monad Data.Semigroup.Option instance GHC.Base.Alternative Data.Semigroup.Option instance GHC.Base.MonadPlus Data.Semigroup.Option instance Control.Monad.Fix.MonadFix Data.Semigroup.Option instance Data.Foldable.Foldable Data.Semigroup.Option instance Data.Traversable.Traversable Data.Semigroup.Option instance Data.Semigroup.Semigroup a => Data.Semigroup.Semigroup (Data.Semigroup.Option a) instance Data.Semigroup.Semigroup a => GHC.Base.Monoid (Data.Semigroup.Option a) instance GHC.Base.Monoid m => Data.Semigroup.Semigroup (Data.Semigroup.WrappedMonoid m) instance GHC.Base.Monoid m => GHC.Base.Monoid (Data.Semigroup.WrappedMonoid m) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.WrappedMonoid a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.Last a) instance Data.Semigroup.Semigroup (Data.Semigroup.Last a) instance GHC.Base.Functor Data.Semigroup.Last instance Data.Foldable.Foldable Data.Semigroup.Last instance Data.Traversable.Traversable Data.Semigroup.Last instance GHC.Base.Applicative Data.Semigroup.Last instance GHC.Base.Monad Data.Semigroup.Last instance Control.Monad.Fix.MonadFix Data.Semigroup.Last instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.First a) instance Data.Semigroup.Semigroup (Data.Semigroup.First a) instance GHC.Base.Functor Data.Semigroup.First instance Data.Foldable.Foldable Data.Semigroup.First instance Data.Traversable.Traversable Data.Semigroup.First instance GHC.Base.Applicative Data.Semigroup.First instance GHC.Base.Monad Data.Semigroup.First instance Control.Monad.Fix.MonadFix Data.Semigroup.First instance GHC.Base.Functor (Data.Semigroup.Arg a) instance Data.Foldable.Foldable (Data.Semigroup.Arg a) instance Data.Traversable.Traversable (Data.Semigroup.Arg a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Arg a b) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Arg a b) instance Data.Bifunctor.Bifunctor Data.Semigroup.Arg instance Data.Bifoldable.Bifoldable Data.Semigroup.Arg instance Data.Bitraversable.Bitraversable Data.Semigroup.Arg instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.Max a) instance GHC.Classes.Ord a => Data.Semigroup.Semigroup (Data.Semigroup.Max a) instance (GHC.Classes.Ord a, GHC.Enum.Bounded a) => GHC.Base.Monoid (Data.Semigroup.Max a) instance GHC.Base.Functor Data.Semigroup.Max instance Data.Foldable.Foldable Data.Semigroup.Max instance Data.Traversable.Traversable Data.Semigroup.Max instance GHC.Base.Applicative Data.Semigroup.Max instance GHC.Base.Monad Data.Semigroup.Max instance Control.Monad.Fix.MonadFix Data.Semigroup.Max instance GHC.Num.Num a => GHC.Num.Num (Data.Semigroup.Max a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.Min a) instance GHC.Classes.Ord a => Data.Semigroup.Semigroup (Data.Semigroup.Min a) instance (GHC.Classes.Ord a, GHC.Enum.Bounded a) => GHC.Base.Monoid (Data.Semigroup.Min a) instance GHC.Base.Functor Data.Semigroup.Min instance Data.Foldable.Foldable Data.Semigroup.Min instance Data.Traversable.Traversable Data.Semigroup.Min instance GHC.Base.Applicative Data.Semigroup.Min instance GHC.Base.Monad Data.Semigroup.Min instance Control.Monad.Fix.MonadFix Data.Semigroup.Min instance GHC.Num.Num a => GHC.Num.Num (Data.Semigroup.Min a) instance Data.Semigroup.Semigroup () instance Data.Semigroup.Semigroup b => Data.Semigroup.Semigroup (a -> b) instance Data.Semigroup.Semigroup [a] instance Data.Semigroup.Semigroup a => Data.Semigroup.Semigroup (GHC.Base.Maybe a) instance Data.Semigroup.Semigroup (Data.Either.Either a b) instance (Data.Semigroup.Semigroup a, Data.Semigroup.Semigroup b) => Data.Semigroup.Semigroup (a, b) instance (Data.Semigroup.Semigroup a, Data.Semigroup.Semigroup b, Data.Semigroup.Semigroup c) => Data.Semigroup.Semigroup (a, b, c) instance (Data.Semigroup.Semigroup a, Data.Semigroup.Semigroup b, Data.Semigroup.Semigroup c, Data.Semigroup.Semigroup d) => Data.Semigroup.Semigroup (a, b, c, d) instance (Data.Semigroup.Semigroup a, Data.Semigroup.Semigroup b, Data.Semigroup.Semigroup c, Data.Semigroup.Semigroup d, Data.Semigroup.Semigroup e) => Data.Semigroup.Semigroup (a, b, c, d, e) instance Data.Semigroup.Semigroup GHC.Types.Ordering instance Data.Semigroup.Semigroup a => Data.Semigroup.Semigroup (Data.Monoid.Dual a) instance Data.Semigroup.Semigroup (Data.Monoid.Endo a) instance Data.Semigroup.Semigroup Data.Monoid.All instance Data.Semigroup.Semigroup Data.Monoid.Any instance GHC.Num.Num a => Data.Semigroup.Semigroup (Data.Monoid.Sum a) instance GHC.Num.Num a => Data.Semigroup.Semigroup (Data.Monoid.Product a) instance Data.Semigroup.Semigroup a => Data.Semigroup.Semigroup (Data.Functor.Identity.Identity a) instance forall k a (b :: k). Data.Semigroup.Semigroup a => Data.Semigroup.Semigroup (Data.Functor.Const.Const a b) instance Data.Semigroup.Semigroup (Data.Monoid.First a) instance Data.Semigroup.Semigroup (Data.Monoid.Last a) instance GHC.Base.Alternative f => Data.Semigroup.Semigroup (Data.Monoid.Alt f a) instance Data.Semigroup.Semigroup Data.Void.Void instance Data.Semigroup.Semigroup (Data.List.NonEmpty.NonEmpty a) instance forall k (s :: k). Data.Semigroup.Semigroup (Data.Proxy.Proxy s) instance Data.Semigroup.Semigroup a => Data.Semigroup.Semigroup (GHC.Types.IO a) instance Data.Semigroup.Semigroup GHC.Event.Internal.Event instance Data.Semigroup.Semigroup GHC.Event.Internal.Lifetime -- | Sums, lifted to functors. module Data.Functor.Sum -- | Lifted sum of functors. data Sum f g a InL :: (f a) -> Sum f g a InR :: (g a) -> Sum f g a instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (Data.Functor.Sum.Sum f g) instance forall k (f :: k -> *) (g :: k -> *) (a :: k). GHC.Generics.Generic (Data.Functor.Sum.Sum f g a) instance forall k (f :: k -> *) (g :: k -> *) (a :: k). (Data.Data.Data (g a), Data.Data.Data (f a), Data.Typeable.Internal.Typeable k, Data.Typeable.Internal.Typeable g, Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable a) => Data.Data.Data (Data.Functor.Sum.Sum f g a) instance (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g) => Data.Functor.Classes.Eq1 (Data.Functor.Sum.Sum f g) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g) => Data.Functor.Classes.Ord1 (Data.Functor.Sum.Sum f g) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g) => Data.Functor.Classes.Read1 (Data.Functor.Sum.Sum f g) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g) => Data.Functor.Classes.Show1 (Data.Functor.Sum.Sum f g) instance (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g, GHC.Classes.Eq a) => GHC.Classes.Eq (Data.Functor.Sum.Sum f g a) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g, GHC.Classes.Ord a) => GHC.Classes.Ord (Data.Functor.Sum.Sum f g a) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g, GHC.Read.Read a) => GHC.Read.Read (Data.Functor.Sum.Sum f g a) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g, GHC.Show.Show a) => GHC.Show.Show (Data.Functor.Sum.Sum f g a) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (Data.Functor.Sum.Sum f g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (Data.Functor.Sum.Sum f g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (Data.Functor.Sum.Sum f g) -- | Products, lifted to functors. module Data.Functor.Product -- | Lifted product of functors. data Product f g a Pair :: (f a) -> (g a) -> Product f g a instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (Data.Functor.Product.Product f g) instance forall k (f :: k -> *) (g :: k -> *) (a :: k). GHC.Generics.Generic (Data.Functor.Product.Product f g a) instance forall k (f :: k -> *) (g :: k -> *) (a :: k). (Data.Data.Data (g a), Data.Data.Data (f a), Data.Typeable.Internal.Typeable k, Data.Typeable.Internal.Typeable g, Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable a) => Data.Data.Data (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g) => Data.Functor.Classes.Eq1 (Data.Functor.Product.Product f g) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g) => Data.Functor.Classes.Ord1 (Data.Functor.Product.Product f g) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g) => Data.Functor.Classes.Read1 (Data.Functor.Product.Product f g) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g) => Data.Functor.Classes.Show1 (Data.Functor.Product.Product f g) instance (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g, GHC.Classes.Eq a) => GHC.Classes.Eq (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g, GHC.Classes.Ord a) => GHC.Classes.Ord (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g, GHC.Read.Read a) => GHC.Read.Read (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g, GHC.Show.Show a) => GHC.Show.Show (Data.Functor.Product.Product f g a) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (Data.Functor.Product.Product f g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (Data.Functor.Product.Product f g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (Data.Functor.Product.Product f g) instance (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (Data.Functor.Product.Product f g) instance (GHC.Base.Alternative f, GHC.Base.Alternative g) => GHC.Base.Alternative (Data.Functor.Product.Product f g) instance (GHC.Base.Monad f, GHC.Base.Monad g) => GHC.Base.Monad (Data.Functor.Product.Product f g) instance (GHC.Base.MonadPlus f, GHC.Base.MonadPlus g) => GHC.Base.MonadPlus (Data.Functor.Product.Product f g) instance (Control.Monad.Fix.MonadFix f, Control.Monad.Fix.MonadFix g) => Control.Monad.Fix.MonadFix (Data.Functor.Product.Product f g) instance (Control.Monad.Zip.MonadZip f, Control.Monad.Zip.MonadZip g) => Control.Monad.Zip.MonadZip (Data.Functor.Product.Product f g) -- | Composition of functors. module Data.Functor.Compose -- | Right-to-left composition of functors. The composition of applicative -- functors is always applicative, but the composition of monads is not -- always a monad. newtype Compose f g a Compose :: f (g a) -> Compose f g a [getCompose] :: Compose f g a -> f (g a) instance forall (f :: * -> *) k (g :: k -> *). GHC.Base.Functor f => GHC.Generics.Generic1 (Data.Functor.Compose.Compose f g) instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). GHC.Generics.Generic (Data.Functor.Compose.Compose f g a) instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). (Data.Data.Data (f (g a)), Data.Typeable.Internal.Typeable k2, Data.Typeable.Internal.Typeable k1, Data.Typeable.Internal.Typeable g, Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable a) => Data.Data.Data (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g) => Data.Functor.Classes.Eq1 (Data.Functor.Compose.Compose f g) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g) => Data.Functor.Classes.Ord1 (Data.Functor.Compose.Compose f g) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g) => Data.Functor.Classes.Read1 (Data.Functor.Compose.Compose f g) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g) => Data.Functor.Classes.Show1 (Data.Functor.Compose.Compose f g) instance (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g, GHC.Classes.Eq a) => GHC.Classes.Eq (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g, GHC.Classes.Ord a) => GHC.Classes.Ord (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g, GHC.Read.Read a) => GHC.Read.Read (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g, GHC.Show.Show a) => GHC.Show.Show (Data.Functor.Compose.Compose f g a) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (Data.Functor.Compose.Compose f g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (Data.Functor.Compose.Compose f g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (Data.Functor.Compose.Compose f g) instance (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (Data.Functor.Compose.Compose f g) instance (GHC.Base.Alternative f, GHC.Base.Applicative g) => GHC.Base.Alternative (Data.Functor.Compose.Compose f g) -- | 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. newtype Fixed a MkFixed :: Integer -> 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 GHC.Classes.Ord (Data.Fixed.Fixed a) instance GHC.Classes.Eq (Data.Fixed.Fixed a) instance Data.Fixed.HasResolution Data.Fixed.E12 instance Data.Fixed.HasResolution Data.Fixed.E9 instance Data.Fixed.HasResolution Data.Fixed.E6 instance Data.Fixed.HasResolution Data.Fixed.E3 instance Data.Fixed.HasResolution Data.Fixed.E2 instance Data.Fixed.HasResolution Data.Fixed.E1 instance Data.Fixed.HasResolution Data.Fixed.E0 instance Data.Fixed.HasResolution a => GHC.Num.Num (Data.Fixed.Fixed a) instance Data.Fixed.HasResolution a => GHC.Real.Real (Data.Fixed.Fixed a) instance Data.Fixed.HasResolution a => GHC.Real.Fractional (Data.Fixed.Fixed a) instance Data.Fixed.HasResolution a => GHC.Real.RealFrac (Data.Fixed.Fixed a) instance Data.Fixed.HasResolution a => GHC.Show.Show (Data.Fixed.Fixed a) instance Data.Fixed.HasResolution a => GHC.Read.Read (Data.Fixed.Fixed a) instance Data.Typeable.Internal.Typeable a => Data.Data.Data (Data.Fixed.Fixed a) instance GHC.Enum.Enum (Data.Fixed.Fixed a) -- | 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. -- -- The Foldable and Traversable instances traverse the real -- part first. 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 :: Complex a -> a -- | Extracts the imaginary part of a complex number. imagPart :: Complex a -> a -- | Form a complex number from polar components of magnitude and phase. mkPolar :: Floating a => a -> a -> Complex a -- | cis t is a complex value with magnitude 1 and -- phase t (modulo 2*pi). cis :: Floating 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 :: Num a => Complex a -> Complex a instance Data.Traversable.Traversable Data.Complex.Complex instance Data.Foldable.Foldable Data.Complex.Complex instance GHC.Base.Functor Data.Complex.Complex instance GHC.Generics.Generic1 Data.Complex.Complex instance GHC.Generics.Generic (Data.Complex.Complex a) instance Data.Data.Data a => Data.Data.Data (Data.Complex.Complex a) instance GHC.Read.Read a => GHC.Read.Read (Data.Complex.Complex a) instance GHC.Show.Show a => GHC.Show.Show (Data.Complex.Complex a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Complex.Complex a) instance GHC.Float.RealFloat a => GHC.Num.Num (Data.Complex.Complex a) instance GHC.Float.RealFloat a => GHC.Real.Fractional (Data.Complex.Complex a) instance GHC.Float.RealFloat a => GHC.Float.Floating (Data.Complex.Complex a) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Data.Complex.Complex a) instance GHC.Base.Applicative Data.Complex.Complex instance GHC.Base.Monad Data.Complex.Complex