-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Basic libraries -- -- This package contains the Standard Haskell 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.19.1.0 -- | Compatibility module for pre ghc-bignum code. module GHC.Integer -- | Arbitrary precision integers. In contrast with fixed-size integral -- types such as Int, the Integer type represents the -- entire infinite range of integers. -- -- Integers are stored in a kind of sign-magnitude form, hence do not -- expect two's complement form when using bit operations. -- -- If the value is small (fit into an Int), IS constructor -- is used. Otherwise IP and IN constructors are used to -- store a BigNat representing respectively the positive or the -- negative value magnitude. -- -- Invariant: IP and IN are used iff value doesn't fit in -- IS data Integer smallInteger :: Int# -> Integer wordToInteger :: Word# -> Integer integerToWord :: Integer -> Word# integerToInt :: Integer -> Int# encodeFloatInteger :: Integer -> Int# -> Float# encodeDoubleInteger :: Integer -> Int# -> Double# decodeDoubleInteger :: Double# -> (# Integer, Int# #) -- | Used to implement (+) for the Num typeclass. This -- gives the sum of two integers. -- --

Example

-- --
--   >>> plusInteger 3 2
--   5
--   
-- --
--   >>> (+) 3 2
--   5
--   
plusInteger :: Integer -> Integer -> Integer -- | Used to implement (-) for the Num typeclass. This -- gives the difference of two integers. -- --

Example

-- --
--   >>> minusInteger 3 2
--   1
--   
-- --
--   >>> (-) 3 2
--   1
--   
minusInteger :: Integer -> Integer -> Integer -- | Used to implement (*) for the Num typeclass. This -- gives the product of two integers. -- --

Example

-- --
--   >>> timesInteger 3 2
--   6
--   
-- --
--   >>> (*) 3 2
--   6
--   
timesInteger :: Integer -> Integer -> Integer -- | Used to implement negate for the Num typeclass. This -- changes the sign of whatever integer is passed into it. -- --

Example

-- --
--   >>> negateInteger (-6)
--   6
--   
-- --
--   >>> negate (-6)
--   6
--   
negateInteger :: Integer -> Integer -- | Used to implement abs for the Num typeclass. This -- gives the absolute value of whatever integer is passed into it. -- --

Example

-- --
--   >>> absInteger (-6)
--   6
--   
-- --
--   >>> abs (-6)
--   6
--   
absInteger :: Integer -> Integer -- | Used to implement signum for the Num typeclass. This -- gives 1 for a positive integer, and -1 for a negative integer. -- --

Example

-- --
--   >>> signumInteger 5
--   1
--   
-- --
--   >>> signum 5
--   1
--   
signumInteger :: Integer -> Integer -- | Used to implement divMod for the Integral typeclass. -- This gives a tuple equivalent to -- --
--   (div x y, mod x y)
--   
-- --

Example

-- --
--   >>> divModInteger 10 2
--   (5,0)
--   
-- --
--   >>> divMod 10 2
--   (5,0)
--   
divModInteger :: Integer -> Integer -> (# Integer, Integer #) -- | Used to implement div for the Integral typeclass. -- This performs integer division on its two parameters, truncated -- towards negative infinity. -- --

Example

-- --
--   >>> 10 `divInteger` 2
--   5
--   
-- --
--   >>> 10 `div` 2
--   
divInteger :: Integer -> Integer -> Integer -- | Used to implement mod for the Integral typeclass. -- This performs the modulo operation, satisfying -- --
--   ((x `div` y) * y) + (x `mod` y) == x
--   
-- --

Example

-- --
--   >>> 7 `modInteger` 3
--   1
--   
-- --
--   >>> 7 `mod` 3
--   1
--   
modInteger :: Integer -> Integer -> Integer -- | Used to implement quotRem for the Integral -- typeclass. This gives a tuple equivalent to -- --
--   (quot x y, mod x y)
--   
-- --

Example

-- --
--   >>> quotRemInteger 10 2
--   (5,0)
--   
-- --
--   >>> quotRem 10 2
--   (5,0)
--   
quotRemInteger :: Integer -> Integer -> (# Integer, Integer #) -- | Used to implement quot for the Integral typeclass. -- This performs integer division on its two parameters, truncated -- towards zero. -- --

Example

-- --
--   >>> quotInteger 10 2
--   5
--   
-- --
--   >>> quot 10 2
--   5
--   
quotInteger :: Integer -> Integer -> Integer -- | Used to implement rem for the Integral typeclass. -- This gives the remainder after integer division of its two parameters, -- satisfying -- --
--   ((x `quot` y) * y) + (x `rem` y) == x
--   
-- --

Example

-- --
--   >>> remInteger 3 2
--   1
--   
-- --
--   >>> rem 3 2
--   1
--   
remInteger :: Integer -> Integer -> Integer -- | Used to implement (==) for the Eq typeclass. Outputs -- True if two integers are equal to each other. -- --

Example

-- --
--   >>> 6 `eqInteger` 6
--   True
--   
-- --
--   >>> 6 == 6
--   True
--   
eqInteger :: Integer -> Integer -> Bool -- | Used to implement (/=) for the Eq typeclass. Outputs -- True if two integers are not equal to each other. -- --

Example

-- --
--   >>> 6 `neqInteger` 7
--   True
--   
-- --
--   >>> 6 /= 7
--   True
--   
neqInteger :: Integer -> Integer -> Bool -- | Used to implement (<=) for the Ord typeclass. -- Outputs True if the first argument is less than or equal to the -- second. -- --

Example

-- --
--   >>> 3 `leInteger` 5
--   True
--   
-- --
--   >>> 3 <= 5
--   True
--   
leInteger :: Integer -> Integer -> Bool -- | Used to implement (>) for the Ord typeclass. -- Outputs True if the first argument is greater than the second. -- --

Example

-- --
--   >>> 5 `gtInteger` 3
--   True
--   
-- --
--   >>> 5 > 3
--   True
--   
gtInteger :: Integer -> Integer -> Bool -- | Used to implement (<) for the Ord typeclass. -- Outputs True if the first argument is less than the second. -- --

Example

-- --
--   >>> 3 `ltInteger` 5
--   True
--   
-- --
--   >>> 3 < 5
--   True
--   
ltInteger :: Integer -> Integer -> Bool -- | Used to implement (>=) for the Ord typeclass. -- Outputs True if the first argument is greater than or equal to -- the second. -- --

Example

-- --
--   >>> 5 `geInteger` 3
--   True
--   
-- --
--   >>> 5 >= 3
--   True
--   
geInteger :: Integer -> Integer -> Bool -- | Used to implement compare for the Integral -- typeclass. This takes two integers, and outputs whether the first is -- less than, equal to, or greater than the second. -- --

Example

-- --
--   >>> compareInteger 2 10
--   LT
--   
-- --
--   >>> compare 2 10
--   LT
--   
compareInteger :: Integer -> Integer -> Ordering eqInteger# :: Integer -> Integer -> Int# neqInteger# :: Integer -> Integer -> Int# leInteger# :: Integer -> Integer -> Int# gtInteger# :: Integer -> Integer -> Int# ltInteger# :: Integer -> Integer -> Int# geInteger# :: Integer -> Integer -> Int# andInteger :: Integer -> Integer -> Integer orInteger :: Integer -> Integer -> Integer xorInteger :: Integer -> Integer -> Integer complementInteger :: Integer -> Integer shiftLInteger :: Integer -> Int# -> Integer shiftRInteger :: Integer -> Int# -> Integer testBitInteger :: Integer -> Int# -> Bool popCountInteger :: Integer -> Int# bitInteger :: Int# -> Integer hashInteger :: Integer -> Int# -- | Compatibility module for pre ghc-bignum code. module GHC.Integer.Logarithms wordLog2# :: Word# -> Int# integerLog2# :: Integer -> Int# integerLogBase# :: Integer -> Integer -> Int# -- | Maybe type module GHC.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 instance GHC.Classes.Eq a => GHC.Classes.Eq (GHC.Maybe.Maybe a) instance GHC.Classes.Ord a => GHC.Classes.Ord (GHC.Maybe.Maybe a) -- | Compatibility module for pre ghc-bignum code. module GHC.Natural -- | Natural number -- -- Invariant: numbers <= 0xffffffffffffffff use the NS -- constructor data Natural pattern NatS# :: Word# -> Natural pattern NatJ# :: BigNat -> Natural -- | A lifted BigNat -- -- Represented as an array of limbs (Word#) stored in little-endian order -- (Word# themselves use machine order). -- -- Invariant (canonical representation): higher Word# is non-zero. -- -- As a consequence, zero is represented with a WordArray# whose size is -- 0. data BigNat BN# :: BigNat# -> BigNat [unBigNat] :: BigNat -> BigNat# -- | Construct Natural value from list of Words. mkNatural :: [Word] -> 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 -- | Natural Addition plusNatural :: Natural -> Natural -> Natural -- | Natural subtraction. May throw -- Underflow. minusNatural :: Natural -> Natural -> Natural -- | Natural subtraction. Returns Nothings for non-positive -- results. minusNaturalMaybe :: Natural -> Natural -> Maybe Natural -- | Natural multiplication timesNatural :: Natural -> Natural -> Natural negateNatural :: Natural -> Natural signumNatural :: Natural -> Natural quotRemNatural :: Natural -> Natural -> (Natural, Natural) quotNatural :: Natural -> Natural -> Natural remNatural :: Natural -> Natural -> Natural -- | Compute greatest common divisor. gcdNatural :: Natural -> Natural -> Natural -- | Compute least common multiple. lcmNatural :: Natural -> Natural -> Natural andNatural :: Natural -> Natural -> Natural orNatural :: Natural -> Natural -> Natural xorNatural :: Natural -> Natural -> Natural bitNatural :: Int# -> Natural testBitNatural :: Natural -> Int -> Bool popCountNatural :: Natural -> Int shiftLNatural :: Natural -> Int -> Natural shiftRNatural :: Natural -> Int -> Natural naturalToInteger :: Natural -> Integer naturalToWord :: Natural -> Word -- | Try downcasting Natural to Word value. Returns -- Nothing if value doesn't fit in Word. naturalToWordMaybe :: Natural -> Maybe Word -- | Construct Natural from Word value. wordToNatural :: Word -> Natural wordToNatural# :: Word -> Natural naturalFromInteger :: Integer -> Natural -- | "powModNatural b e m" computes -- base b raised to exponent e modulo -- m. powModNatural :: Natural -> Natural -> Natural -> Natural -- | type definitions for implicit call-stacks. Use GHC.Stack from -- the base package instead of importing this module directly. module GHC.Stack.Types -- | 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 -- --
--   putStrLnWithCallStack :: HasCallStack => String -> IO ()
--   
-- -- as a variant of putStrLn that will get its call-site and -- print it, along with the string given as argument. We can access the -- call-stack inside putStrLnWithCallStack with -- callStack. -- --
--   >>> :{
--   putStrLnWithCallStack :: HasCallStack => String -> IO ()
--   putStrLnWithCallStack msg = do
--     putStrLn msg
--     putStrLn (prettyCallStack callStack)
--   :}
--   
-- -- Thus, if we call putStrLnWithCallStack we will get a -- formatted call-stack alongside our string. -- --
--   >>> putStrLnWithCallStack "hello"
--   hello
--   CallStack (from HasCallStack):
--     putStrLnWithCallStack, called at <interactive>:... in interactive:Ghci...
--   
-- -- 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 EmptyCallStack :: CallStack PushCallStack :: [Char] -> SrcLoc -> CallStack -> CallStack -- | Freeze the stack at the given CallStack, preventing any -- further call-sites from being pushed onto it. FreezeCallStack :: CallStack -> 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 -- | 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)] -- | Push a call-site onto the stack. -- -- This function has no effect on a frozen CallStack. pushCallStack :: ([Char], SrcLoc) -> CallStack -> CallStack -- | 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 instance GHC.Classes.Eq GHC.Stack.Types.SrcLoc -- | The GHC.Err module defines the code for the wired-in error -- functions, which have a special type in the compiler (with "open -- tyvars"). -- -- We cannot define these functions in a module where they might be used -- (e.g., GHC.Base), because the magical wired-in type will get -- confused with what the typechecker figures out. module GHC.Err -- | Used for compiler-generated error message; encoding saves bytes of -- string junk. absentErr :: a -- | error stops execution and displays an error message. error :: HasCallStack => [Char] -> a -- | A variant of error that does not produce a stack trace. errorWithoutStackTrace :: [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 :: HasCallStack => a -- | Basic data types and classes. module GHC.Base -- | String is an alias for a list of characters. -- -- String constants in Haskell are values of type String. That -- means if you write a string literal like "hello world", it -- will have the type [Char], which is the same as -- String. -- -- Note: You can ask the compiler to automatically infer different -- types with the -XOverloadedStrings language extension, for -- example "hello world" :: Text. See IsString for more -- information. -- -- Because String is just a list of characters, you can use -- normal list functions to do basic string manipulation. See -- Data.List for operations on lists. -- --

Performance considerations

-- -- [Char] is a relatively memory-inefficient type. It is a -- linked list of boxed word-size characters, internally it looks -- something like: -- --
--   ╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭────╮
--   │ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ [] │
--   ╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰────╯
--           v               v               v
--          'a'             'b'             'c'
--   
-- -- The String "abc" will use 5*3+1 = 16 (in general -- 5n+1) words of space in memory. -- -- Furthermore, operations like (++) (string concatenation) are -- O(n) (in the left argument). -- -- For historical reasons, the base library uses String -- in a lot of places for the conceptual simplicity, but library code -- dealing with user-data should use the text package for Unicode -- text, or the the bytestring package for binary data. type String = [Char] -- | 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: -- -- -- -- 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 :: Type -> Type) -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. -- -- 'as >>= bs' can be understood as the do -- expression -- --
--   do a <- as
--      bs a
--   
(>>=) :: 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. -- -- 'as >> bs' can be understood as the do -- expression -- --
--   do as
--      bs
--   
(>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a infixl 1 >>= infixl 1 >> -- | 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 :: Type -> Type) -- | 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. -- --

Example

-- -- Used in combination with (<$>), -- (<*>) can be used to build a record. -- --
--   >>> data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
--   
-- --
--   >>> produceFoo :: Applicative f => f Foo
--   
-- --
--   >>> produceBar :: Applicative f => f Bar
--   
--   >>> produceBaz :: Applicative f => f Baz
--   
-- --
--   >>> mkState :: Applicative f => f MyState
--   
--   >>> mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz
--   
(<*>) :: 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 <*>. -- -- This became a typeclass method in 4.10.0.0. Prior to that, it was a -- function defined in terms of <*> and fmap. -- --

Example

-- --
--   >>> liftA2 (,) (Just 3) (Just 5)
--   Just (3,5)
--   
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c -- | Sequence actions, discarding the value of the first argument. -- --

Examples

-- -- If used in conjunction with the Applicative instance for Maybe, -- you can chain Maybe computations, with a possible "early return" in -- case of Nothing. -- --
--   >>> Just 2 *> Just 3
--   Just 3
--   
-- --
--   >>> Nothing *> Just 3
--   Nothing
--   
-- -- Of course a more interesting use case would be to have effectful -- computations instead of just returning pure values. -- --
--   >>> import Data.Char
--   
--   >>> import Text.ParserCombinators.ReadP
--   
--   >>> let p = string "my name is " *> munch1 isAlpha <* eof
--   
--   >>> readP_to_S p "my name is Simon"
--   [("Simon","")]
--   
(*>) :: 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 infixl 4 <*> infixl 4 *> infixl 4 <* -- | Right to left function composition. -- --
--   (f . g) x = f (g x)
--   
-- --
--   f . id = f = id . f
--   
-- --

Examples

-- --
--   >>> map ((*2) . length) [[], [0, 1, 2], [0]]
--   [0,6,2]
--   
-- --
--   >>> foldr (.) id [(+1), (*3), (^3)] 2
--   25
--   
-- --
--   >>> let (...) = (.).(.) in ((*2)...(+)) 5 10
--   30
--   
(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | A monoid on applicative functors. -- -- If defined, some and many should be the least solutions -- of the equations: -- -- class Applicative f => Alternative (f :: Type -> Type) -- | 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] infixl 3 <|> -- | A type f is a Functor if it provides a function fmap -- which, given any types a and b lets you apply any -- function from (a -> b) to turn an f a into an -- f b, preserving the structure of f. Furthermore -- f needs to adhere to the following: -- -- -- -- Note, that the second law follows from the free theorem of the type -- fmap and the first law, so you need only check that the former -- condition holds. See -- https://www.schoolofhaskell.com/user/edwardk/snippets/fmap or -- https://github.com/quchen/articles/blob/master/second_functor_law.md -- for an explanation. class Functor (f :: Type -> Type) -- | fmap is used to apply a function of type (a -> b) -- to a value of type f a, where f is a functor, to produce a -- value of type f b. Note that for any type constructor with -- more than one parameter (e.g., Either), only the last type -- parameter can be modified with fmap (e.g., b in -- `Either a b`). -- -- Some type constructors with two parameters or more have a -- Bifunctor instance that allows both the last and the -- penultimate parameters to be mapped over. -- --

Examples

-- -- Convert from a Maybe Int to a Maybe String -- using show: -- --
--   >>> fmap show Nothing
--   Nothing
--   
--   >>> fmap show (Just 3)
--   Just "3"
--   
-- -- Convert from an Either Int Int to an Either Int -- String using show: -- --
--   >>> fmap show (Left 17)
--   Left 17
--   
--   >>> fmap show (Right 17)
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> fmap (*2) [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> fmap even (2,2)
--   (2,True)
--   
-- -- It may seem surprising that the function is only applied to the last -- element of the tuple compared to the list example above which applies -- it to every element in the list. To understand, remember that tuples -- are type constructors with multiple type parameters: a tuple of 3 -- elements (a,b,c) can also be written (,,) a b c and -- its Functor instance is defined for Functor ((,,) a -- b) (i.e., only the third parameter is free to be mapped over with -- fmap). -- -- It explains why fmap can be used with tuples containing -- values of different types as in the following example: -- --
--   >>> fmap even ("hello", 1.0, 4)
--   ("hello",1.0,True)
--   
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. -- --

Examples

-- -- Perform a computation with Maybe and replace the result with a -- constant value if it is Just: -- --
--   >>> 'a' <$ Just 2
--   Just 'a'
--   
--   >>> 'a' <$ Nothing
--   Nothing
--   
(<$) :: Functor f => a -> f b -> f a infixl 4 <$ -- | A variant of <*> with the types of the arguments -- reversed. It differs from flip (<*>) in -- that the effects are resolved in the order the arguments are -- presented. -- --

Examples

-- --
--   >>> (<**>) (print 1) (id <$ print 2)
--   1
--   2
--   
-- --
--   >>> flip (<*>) (print 1) (id <$ print 2)
--   2
--   1
--   
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 <**> -- | Lift a function to actions. Equivalent to Functor's fmap but -- implemented using only Applicative's methods: liftA -- f a = pure f <*> a -- -- As such this function may be used to implement a Functor -- instance from an Applicative one. -- --

Examples

-- -- Using the Applicative instance for Lists: -- --
--   >>> liftA (+1) [1, 2]
--   [2,3]
--   
-- -- Or the Applicative instance for Maybe -- --
--   >>> liftA (+1) (Just 3)
--   Just 4
--   
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 -- | Identity function. -- --
--   id x = x
--   
-- -- This function might seem useless at first glance, but it can be very -- useful in a higher order context. -- --

Examples

-- --
--   >>> length $ filter id [True, True, False, True]
--   3
--   
-- --
--   >>> Just (Just 3) >>= id
--   Just 3
--   
-- --
--   >>> foldr id 0 [(^3), (*5), (+2)]
--   1000
--   
id :: a -> a -- | 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 () -- | 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 -- | Monads that also support choice and failure. class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) -- | The identity of mplus. It should also satisfy the equations -- --
--   mzero >>= f  =  mzero
--   v >> mzero   =  mzero
--   
-- -- The default definition is -- --
--   mzero = empty
--   
mzero :: MonadPlus m => m a -- | An associative operation. The default definition is -- --
--   mplus = (<|>)
--   
mplus :: MonadPlus m => m a -> m a -> m a -- | mapM f is equivalent to sequence . -- map f. mapM :: Monad m => (a -> m b) -> [a] -> m [b] -- | Evaluate each action in the sequence from left to right, and collect -- the results. sequence :: Monad m => [m a] -> m [a] -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | 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 bss' can be understood as the do -- expression -- --
--   do bs <- bss
--      bs
--   
-- --

Examples

-- -- A common use of join is to run an IO computation -- returned from an STM transaction, since STM transactions -- can't perform IO directly. Recall that -- --
--   atomically :: STM a -> IO a
--   
-- -- is used to run STM transactions atomically. So, by specializing -- the types of atomically and join to -- --
--   atomically :: STM (IO b) -> IO (IO b)
--   join       :: IO (IO b)  -> IO b
--   
-- -- we can compose them as -- --
--   join . atomically :: STM (IO b) -> IO b
--   
-- -- to run an STM transaction and the IO action it returns. join :: Monad m => m (m a) -> m a -- | 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 failIO :: String -> IO a -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following: -- -- -- -- You can alternatively define mconcat instead of mempty, -- in which case the laws are: -- -- -- -- 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. -- -- NOTE: Semigroup is a superclass of Monoid since -- base-4.11.0.0. class Semigroup a => Monoid a -- | Identity of mappend -- --

Examples

-- --
--   >>> "Hello world" <> mempty
--   "Hello world"
--   
-- --
--   >>> mempty <> [1, 2, 3]
--   [1,2,3]
--   
mempty :: Monoid a => a -- | An associative operation -- -- NOTE: This method is redundant and has the default -- implementation mappend = (<>) since -- base-4.11.0.0. Should it be implemented manually, since -- mappend is a synonym for (<>), it is expected that -- the two functions are defined the same way. In a future GHC release -- mappend will be removed from Monoid. 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 ["Hello", " ", "Haskell", "!"]
--   "Hello Haskell!"
--   
mconcat :: Monoid a => [a] -> a -- | Non-empty (and non-strict) list type. data NonEmpty a (:|) :: a -> [a] -> NonEmpty a infixr 5 :| -- | ($) is the function application operator. -- -- Applying ($) to a function f and an argument -- x gives the same result as applying f to x -- directly. The definition is akin to this: -- --
--   ($) :: (a -> b) -> a -> b
--   ($) f x = f x
--   
-- -- This is id specialized from a -> a to -- (a -> b) -> (a -> b) which by the associativity of -- (->) is the same as (a -> b) -> a -> b. -- -- On the face of it, this may appear pointless! But it's actually one of -- the most useful and important operators in Haskell. -- -- The order of operations is very different between ($) and -- normal function application. Normal function application has -- precedence 10 - higher than any operator - and associates to the left. -- So these two definitions are equivalent: -- --
--   expr = min 5 1 + 5
--   expr = ((min 5) 1) + 5
--   
-- -- ($) has precedence 0 (the lowest) and associates to the -- right, so these are equivalent: -- --
--   expr = min 5 $ 1 + 5
--   expr = (min 5) (1 + 5)
--   
-- --

Examples

-- -- A common use cases of ($) is to avoid parentheses in complex -- expressions. -- -- For example, instead of using nested parentheses in the following -- Haskell function: -- --
--   -- | Sum numbers in a string: strSum "100  5 -7" == 98
--   strSum :: String -> Int
--   strSum s = sum (mapMaybe readMaybe (words s))
--   
-- -- we can deploy the function application operator: -- --
--   -- | Sum numbers in a string: strSum "100  5 -7" == 98
--   strSum :: String -> Int
--   strSum s = sum $ mapMaybe readMaybe $ words s
--   
-- -- ($) is also used as a section (a partially applied operator), -- in order to indicate that we wish to apply some yet-unspecified -- function to a given value. For example, to apply the argument -- 5 to a list of functions: -- --
--   applyFive :: [Int]
--   applyFive = map ($ 5) [(+1), (2^)]
--   >>> [6, 32]
--   
-- --

Technical Remark (Representation Polymorphism)

-- -- ($) is fully representation-polymorphic. This allows it to -- also be used with arguments of unlifted and even unboxed kinds, such -- as unboxed integers: -- --
--   fastMod :: Int -> Int -> Int
--   fastMod (I# x) (I# m) = I# $ remInt# x m
--   
($) :: (a -> b) -> a -> b infixr 0 $ -- | The class of semigroups (types with an associative binary operation). -- -- Instances should satisfy the following: -- -- -- -- You can alternatively define sconcat instead of -- (<>), in which case the laws are: -- -- class Semigroup a -- | An associative operation. -- --

Examples

-- --
--   >>> [1,2,3] <> [4,5,6]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> Just [1, 2, 3] <> Just [4, 5, 6]
--   Just [1,2,3,4,5,6]
--   
-- --
--   >>> putStr "Hello, " <> putStrLn "World!"
--   Hello, World!
--   
(<>) :: Semigroup a => a -> a -> a -- | Reduce a non-empty list with <> -- -- The default definition should be sufficient, but this can be -- overridden for efficiency. -- --

Examples

-- -- For the following examples, we will assume that we have: -- --
--   >>> import Data.List.NonEmpty (NonEmpty (..))
--   
-- --
--   >>> sconcat $ "Hello" :| [" ", "Haskell", "!"]
--   "Hello Haskell!"
--   
-- --
--   >>> sconcat $ Just [1, 2, 3] :| [Nothing, Just [4, 5, 6]]
--   Just [1,2,3,4,5,6]
--   
-- --
--   >>> sconcat $ Left 1 :| [Right 2, Left 3, Right 4]
--   Right 2
--   
sconcat :: Semigroup a => NonEmpty a -> a -- | Repeat a value n times. -- -- The default definition will raise an exception for a multiplier that -- is <= 0. This may be overridden with an implementation -- that is total. For monoids it is preferred to use -- stimesMonoid. -- -- By making this a member of the class, idempotent semigroups and -- monoids can upgrade this to execute in <math> by picking -- stimes = stimesIdempotent or stimes = -- stimesIdempotentMonoid respectively. -- --

Examples

-- --
--   >>> stimes 4 [1]
--   [1,1,1,1]
--   
-- --
--   >>> stimes 5 (putStr "hi!")
--   hi!hi!hi!hi!hi!
--   
-- --
--   >>> stimes 3 (Right ":)")
--   Right ":)"
--   
stimes :: (Semigroup a, Integral b) => b -> a -> a infixr 6 <> -- | otherwise is defined as the value True. It helps to make -- guards more readable. eg. -- --
--   f x | x < 0     = ...
--       | otherwise = ...
--   
otherwise :: Bool -- | The fromEnum method restricted to the type Char. ord :: Char -> Int -- | 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 -- | 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 $! -- | flip f takes its (first) two arguments in the reverse -- order of f. -- --
--   flip f x y = f y x
--   
-- --
--   flip . flip = id
--   
-- --

Examples

-- --
--   >>> flip (++) "hello" "world"
--   "worldhello"
--   
-- --
--   >>> let (.>) = flip (.) in (+1) .> show $ 5
--   "6"
--   
flip :: (a -> b -> c) -> b -> a -> c -- | const x y always evaluates to x, ignoring its second -- argument. -- --
--   const x = \_ -> x
--   
-- -- This function might seem useless at first glance, but it can be very -- useful in a higher order context. -- --

Examples

-- --
--   >>> const 42 "hello"
--   42
--   
-- --
--   >>> map (const 42) [0..3]
--   [42,42,42,42]
--   
const :: a -> b -> a -- | (++) appends 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. -- --

Performance considerations

-- -- This function takes linear time in the number of elements of the -- first list. Thus it is better to associate repeated -- applications of (++) to the right (which is the default -- behaviour): xs ++ (ys ++ zs) or simply xs ++ ys ++ -- zs, but not (xs ++ ys) ++ zs. For the same reason -- concat = foldr (++) [] has -- linear performance, while foldl (++) [] is -- prone to quadratic slowdown -- --

Examples

-- --
--   >>> [1, 2, 3] ++ [4, 5, 6]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> [] ++ [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> [3, 2, 1] ++ []
--   [3,2,1]
--   
(++) :: [a] -> [a] -> [a] infixr 5 ++ -- | <math>. 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, ...]
--   
-- -- this means that map id == id -- --

Examples

-- --
--   >>> map (+1) [1, 2, 3]
--   [2,3,4]
--   
-- --
--   >>> map id [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> map (\n -> 3 * n + 1) [1, 2, 3]
--   [4,7,10]
--   
map :: (a -> b) -> [a] -> [b] -- | Uninhabited data type data Void -- | Since Void values logically don't exist, this witnesses the -- logical reasoning tool of "ex falso quodlibet". -- --
--   >>> let x :: Either Void Int; x = Right 5
--   
--   >>> :{
--   case x of
--       Right r -> r
--       Left l  -> absurd l
--   :}
--   5
--   
absurd :: Void -> a -- | If Void is uninhabited then any Functor that holds only -- values of type Void is holding no values. It is implemented in -- terms of fmap absurd. vacuous :: Functor f => f Void -> f a -- | 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# -- | A list producer that can be fused with foldr. This function is -- merely -- --
--   build g = g (:) []
--   
-- -- but GHC's simplifier will transform an expression of the form -- foldr k z (build g), which may arise after -- inlining, to g k z, which avoids producing an intermediate -- list. build :: (forall b. () => (a -> b -> b) -> b -> b) -> [a] -- | A list producer that can be fused with foldr. This function is -- merely -- --
--   augment g xs = g (:) xs
--   
-- -- but GHC's simplifier will transform an expression of the form -- foldr k z (augment g xs), which may arise after -- inlining, to g k (foldr k z xs), which avoids -- producing an intermediate list. augment :: (forall b. () => (a -> b -> b) -> b -> b) -> [a] -> [a] breakpoint :: a -> a breakpointCond :: Bool -> a -> a unIO :: IO a -> State# RealWorld -> (# State# RealWorld, a #) -- | 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 -- | This String equality predicate is used when desugaring -- pattern-matches against strings. eqString :: String -> String -> Bool returnIO :: a -> IO a bindIO :: IO a -> (a -> IO b) -> IO b thenIO :: IO a -> IO b -> IO b mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst unsafeChr :: Int -> Char maxInt :: Int minInt :: Int data Opaque O :: a -> Opaque -- | Returns the tag of a constructor application; this function is used by -- the deriving code for Eq, Ord and Enum. getTag :: a -> Int# -- | Used to implement quot for the Integral typeclass. -- This performs integer division on its two parameters, truncated -- towards zero. -- --

Example

-- --
--   >>> quotInt 10 2
--   5
--   
-- --
--   >>> quot 10 2
--   5
--   
quotInt :: Int -> Int -> Int -- | Used to implement rem for the Integral typeclass. This -- gives the remainder after integer division of its two parameters, -- satisfying -- --
--   ((x `quot` y) * y) + (x `rem` y) == x
--   
-- --

Example

-- --
--   >>> remInt 3 2
--   1
--   
-- --
--   >>> rem 3 2
--   1
--   
remInt :: Int -> Int -> Int -- | Used to implement div for the Integral typeclass. This -- performs integer division on its two parameters, truncated towards -- negative infinity. -- --

Example

-- --
--   >>> 10 `divInt` 2
--   5
--   
-- --
--   >>> 10 `div` 2
--   5
--   
divInt :: Int -> Int -> Int -- | Used to implement mod for the Integral typeclass. This -- performs the modulo operation, satisfying -- --
--   ((x `div` y) * y) + (x `mod` y) == x
--   
-- --

Example

-- --
--   >>> 7 `modInt` 3
--   1
--   
-- --
--   >>> 7 `mod` 3
--   1
--   
modInt :: Int -> Int -> Int -- | Used to implement quotRem for the Integral typeclass. -- This gives a tuple equivalent to -- --
--   (quot x y, mod x y)
--   
-- --

Example

-- --
--   >>> quotRemInt 10 2
--   (5,0)
--   
-- --
--   >>> quotRem 10 2
--   (5,0)
--   
quotRemInt :: Int -> Int -> (Int, Int) -- | Used to implement divMod for the Integral typeclass. -- This gives a tuple equivalent to -- --
--   (div x y, mod x y)
--   
-- --

Example

-- --
--   >>> divModInt 10 2
--   (5,0)
--   
-- --
--   >>> divMod 10 2
--   (5,0)
--   
divModInt :: Int -> Int -> (Int, Int) -- | This function is used to implement branchless shifts. If the number of -- bits to shift is greater than or equal to the type size in bits, then -- the shift must return 0. Instead of doing a test, we use a mask -- obtained via this function which is branchless too. -- -- shift_mask m b | b < m = 0xFF..FF | otherwise = 0 shift_mask :: Int# -> Int# -> Int# data TYPE (a :: RuntimeRep) data CONSTRAINT (a :: RuntimeRep) rightSection :: forall {n :: Multiplicity} {o :: Multiplicity} a b c. (a %n -> b %o -> c) -> b %o -> a %n -> c leftSection :: forall {n :: Multiplicity} a b. (a %n -> b) -> a %n -> b instance GHC.Base.Alternative GHC.Types.IO instance GHC.Base.Alternative [] instance GHC.Base.Alternative GHC.Maybe.Maybe instance GHC.Base.Applicative ((->) r) instance GHC.Base.Applicative GHC.Types.IO instance GHC.Base.Applicative [] instance GHC.Base.Applicative GHC.Maybe.Maybe instance GHC.Base.Applicative GHC.Base.NonEmpty instance GHC.Base.Applicative GHC.Tuple.Prim.Solo instance GHC.Base.Monoid a => GHC.Base.Applicative ((,) a) instance (GHC.Base.Monoid a, GHC.Base.Monoid b) => GHC.Base.Applicative ((,,) a b) instance (GHC.Base.Monoid a, GHC.Base.Monoid b, GHC.Base.Monoid c) => GHC.Base.Applicative ((,,,) a b c) instance GHC.Classes.Eq a => GHC.Classes.Eq (GHC.Base.NonEmpty a) instance GHC.Classes.Eq GHC.Base.Void instance GHC.Base.Functor ((->) r) instance GHC.Base.Functor GHC.Types.IO instance GHC.Base.Functor [] instance GHC.Base.Functor GHC.Maybe.Maybe instance GHC.Base.Functor GHC.Base.NonEmpty instance GHC.Base.Functor GHC.Tuple.Prim.Solo instance GHC.Base.Functor ((,) a) instance GHC.Base.Functor ((,,) a b) instance GHC.Base.Functor ((,,,) a b c) instance GHC.Base.Functor ((,,,,) a b c d) instance GHC.Base.Functor ((,,,,,) a b c d e) instance GHC.Base.Functor ((,,,,,,) a b c d e f) instance GHC.Base.MonadPlus GHC.Types.IO instance GHC.Base.MonadPlus [] instance GHC.Base.MonadPlus GHC.Maybe.Maybe instance GHC.Base.Monad ((->) r) instance GHC.Base.Monad GHC.Types.IO instance GHC.Base.Monad [] instance GHC.Base.Monad GHC.Maybe.Maybe instance GHC.Base.Monad GHC.Base.NonEmpty instance GHC.Base.Monad GHC.Tuple.Prim.Solo instance GHC.Base.Monoid a => GHC.Base.Monad ((,) a) instance (GHC.Base.Monoid a, GHC.Base.Monoid b) => GHC.Base.Monad ((,,) a b) instance (GHC.Base.Monoid a, GHC.Base.Monoid b, GHC.Base.Monoid c) => GHC.Base.Monad ((,,,) a b c) instance GHC.Base.Monoid b => GHC.Base.Monoid (a -> b) instance GHC.Base.Monoid a => GHC.Base.Monoid (GHC.Types.IO a) instance GHC.Base.Monoid [a] instance GHC.Base.Semigroup a => GHC.Base.Monoid (GHC.Maybe.Maybe a) instance GHC.Base.Monoid GHC.Types.Ordering instance GHC.Base.Monoid a => GHC.Base.Monoid (GHC.Tuple.Prim.Solo a) instance (GHC.Base.Monoid a, GHC.Base.Monoid b) => GHC.Base.Monoid (a, b) instance (GHC.Base.Monoid a, GHC.Base.Monoid b, GHC.Base.Monoid c) => GHC.Base.Monoid (a, b, c) instance (GHC.Base.Monoid a, GHC.Base.Monoid b, GHC.Base.Monoid c, GHC.Base.Monoid d) => GHC.Base.Monoid (a, b, c, d) instance (GHC.Base.Monoid a, GHC.Base.Monoid b, GHC.Base.Monoid c, GHC.Base.Monoid d, GHC.Base.Monoid e) => GHC.Base.Monoid (a, b, c, d, e) instance GHC.Base.Monoid () instance GHC.Classes.Ord a => GHC.Classes.Ord (GHC.Base.NonEmpty a) instance GHC.Classes.Ord GHC.Base.Void instance GHC.Base.Semigroup b => GHC.Base.Semigroup (a -> b) instance GHC.Base.Semigroup a => GHC.Base.Semigroup (GHC.Types.IO a) instance GHC.Base.Semigroup [a] instance GHC.Base.Semigroup a => GHC.Base.Semigroup (GHC.Maybe.Maybe a) instance GHC.Base.Semigroup (GHC.Base.NonEmpty a) instance GHC.Base.Semigroup GHC.Types.Ordering instance GHC.Base.Semigroup a => GHC.Base.Semigroup (GHC.Tuple.Prim.Solo a) instance (GHC.Base.Semigroup a, GHC.Base.Semigroup b) => GHC.Base.Semigroup (a, b) instance (GHC.Base.Semigroup a, GHC.Base.Semigroup b, GHC.Base.Semigroup c) => GHC.Base.Semigroup (a, b, c) instance (GHC.Base.Semigroup a, GHC.Base.Semigroup b, GHC.Base.Semigroup c, GHC.Base.Semigroup d) => GHC.Base.Semigroup (a, b, c, d) instance (GHC.Base.Semigroup a, GHC.Base.Semigroup b, GHC.Base.Semigroup c, GHC.Base.Semigroup d, GHC.Base.Semigroup e) => GHC.Base.Semigroup (a, b, c, d, e) instance GHC.Base.Semigroup () instance GHC.Base.Semigroup GHC.Base.Void module GHC.Profiling -- | Start attributing ticks to cost centres. This is called by the RTS on -- startup. startProfTimer :: IO () -- | Stop attributing ticks to cost centres. Allocations will still be -- attributed. stopProfTimer :: IO () -- | Start heap profiling. This is called normally by the RTS on start-up, -- but can be disabled using the rts flag `--no-automatic-heap-samples` -- Note: This won't do anything unless you also specify a profiling mode -- on the command line using the normal RTS options. startHeapProfTimer :: IO () -- | Stop heap profiling. Note: This won't do anything unless you also -- specify a profiling mode on the command line using the normal RTS -- options. stopHeapProfTimer :: IO () -- | Request a heap census on the next context switch. The census can be -- requested whether or not the heap profiling timer is running. Note: -- This won't do anything unless you also specify a profiling mode on the -- command line using the normal RTS options. requestHeapCensus :: IO () -- | The Num class and the Integer type. module GHC.Num -- | Basic numeric class. -- -- The Haskell Report defines no laws for Num. However, -- (+) and (*) are customarily expected -- to define a ring and have the following properties: -- -- -- -- Note that it isn't customarily expected that a type instance of -- both Num and Ord implement an ordered ring. Indeed, in -- base only Integer and Rational do. 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 infixl 6 - infixl 6 + infixl 7 * -- | Deprecated: Use integerQuotRem# instead quotRemInteger :: Integer -> Integer -> (# Integer, Integer #) -- | 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 -- | Natural number -- -- Invariant: numbers <= 0xffffffffffffffff use the NS -- constructor data Natural -- | Arbitrary precision integers. In contrast with fixed-size integral -- types such as Int, the Integer type represents the -- entire infinite range of integers. -- -- Integers are stored in a kind of sign-magnitude form, hence do not -- expect two's complement form when using bit operations. -- -- If the value is small (fit into an Int), IS constructor -- is used. Otherwise IP and IN constructors are used to -- store a BigNat representing respectively the positive or the -- negative value magnitude. -- -- Invariant: IP and IN are used iff value doesn't fit in -- IS data Integer instance GHC.Num.Num GHC.Types.Int instance GHC.Num.Num GHC.Num.Integer.Integer instance GHC.Num.Num GHC.Num.Natural.Natural instance GHC.Num.Num GHC.Types.Word -- | The MVar type module GHC.MVar -- | An MVar (pronounced "em-var") is a synchronising variable, used -- for communication between concurrent threads. It can be thought of as -- a box, which may be empty or full. data MVar a MVar :: MVar# RealWorld a -> MVar a -- | Create an MVar which contains the supplied value. newMVar :: a -> IO (MVar a) -- | Create an MVar which is initially empty. newEmptyMVar :: 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 -- | Atomically read the contents of an MVar. If the MVar is -- currently empty, readMVar will wait until it is 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 -- | 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 () -- | 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 -- | 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) -- | 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 -- | Add a finalizer to an MVar (GHC only). See -- Foreign.ForeignPtr and System.Mem.Weak for more about -- finalizers. addMVarFinalizer :: MVar a -> IO () -> IO () instance GHC.Classes.Eq (GHC.MVar.MVar a) -- | Unsafe IO operations module GHC.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! -- -- WARNING: If you're looking for "a way to get a String from an -- 'IO String'", then unsafePerformIO is not the way to go. Learn -- about do-notation and the <- syntax element before you -- proceed. unsafePerformIO :: 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 -- | 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 -- | unsafeDupableInterleaveIO 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. -- -- The computation may be performed multiple times by different threads, -- possibly at the same time. To ensure that the computation is performed -- only once, use unsafeInterleaveIO instead. unsafeDupableInterleaveIO :: IO a -> IO a -- | Ensures that the suspensions under evaluation by the current thread -- are unique; that is, the current thread is not evaluating anything -- that is also under evaluation by another thread that has also executed -- noDuplicate. -- -- This operation is used in the definition of unsafePerformIO to -- prevent the IO action from being executed multiple times, which is -- usually undesirable. noDuplicate :: IO () module GHC.IO.Encoding.CodePage -- | The GHCi Monad lifting interface. -- -- EXPERIMENTAL! DON'T USE. -- | Warning: This is an unstable interface. module GHC.GHCi -- | A monad that can execute GHCi statements by lifting them out of m into -- the IO monad. (e.g state monads) class Monad m => GHCiSandboxIO (m :: Type -> Type) ghciStepIO :: GHCiSandboxIO m => m a -> IO a -- | A monad that doesn't allow any IO. data NoIO a instance GHC.Base.Applicative GHC.GHCi.NoIO instance GHC.Base.Functor GHC.GHCi.NoIO instance GHC.GHCi.GHCiSandboxIO GHC.Types.IO instance GHC.GHCi.GHCiSandboxIO GHC.GHCi.NoIO instance GHC.Base.Monad GHC.GHCi.NoIO -- | Methods for the RealFrac instances for Float and Double, -- with specialised versions for Int. -- -- Moved to their own module to not bloat GHC.Float further. module GHC.Float.RealFracMethods properFractionDoubleInteger :: Double -> (Integer, Double) truncateDoubleInteger :: Double -> Integer floorDoubleInteger :: Double -> Integer ceilingDoubleInteger :: Double -> Integer roundDoubleInteger :: Double -> Integer properFractionDoubleInt :: Double -> (Int, Double) floorDoubleInt :: Double -> Int ceilingDoubleInt :: Double -> Int roundDoubleInt :: Double -> Int double2Int :: Double -> Int int2Double :: Int -> Double properFractionFloatInteger :: Float -> (Integer, Float) truncateFloatInteger :: Float -> Integer floorFloatInteger :: Float -> Integer ceilingFloatInteger :: Float -> Integer roundFloatInteger :: Float -> Integer properFractionFloatInt :: Float -> (Int, Float) floorFloatInt :: Float -> Int ceilingFloatInt :: Float -> Int roundFloatInt :: Float -> Int float2Int :: Float -> Int int2Float :: Int -> Float -- | Utilities for conversion between Double/Float and Rational module GHC.Float.ConversionUtils elimZerosInteger :: Integer -> Int# -> (# Integer, Int# #) elimZerosInt# :: Int# -> Int# -> (# Integer, Int# #) 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 -- | Solo is the canonical lifted 1-tuple, just like (,) is -- the canonical lifted 2-tuple (pair) and (,,) is the canonical -- lifted 3-tuple (triple). -- -- The most important feature of Solo is that it is possible to -- force its "outside" (usually by pattern matching) without forcing its -- "inside", because it is defined as a datatype rather than a newtype. -- One situation where this can be useful is when writing a function to -- extract a value from a data structure. Suppose you write an -- implementation of arrays and offer only this function to index into -- them: -- --
--   index :: Array a -> Int -> a
--   
-- -- Now imagine that someone wants to extract a value from an array and -- store it in a lazy-valued finite map/dictionary: -- --
--   insert "hello" (arr index 12) m
--   
-- -- This can actually lead to a space leak. The value is not actually -- extracted from the array until that value (now buried in a map) is -- forced. That means the entire array may be kept live by just that -- value! Often, the solution is to use a strict map, or to force the -- value before storing it, but for some purposes that's undesirable. -- -- One common solution is to include an indexing function that can -- produce its result in an arbitrary Applicative context: -- --
--   indexA :: Applicative f => Array a -> Int -> f a
--   
-- -- When using indexA in a pure context, Solo -- serves as a handy Applicative functor to hold the result. You -- could write a non-leaky version of the above example thus: -- --
--   case arr indexA 12 of
--     Solo a -> insert "hello" a m
--   
-- -- While such simple extraction functions are the most common uses for -- unary tuples, they can also be useful for fine-grained control of -- strict-spined data structure traversals, and for unifying the -- implementations of lazy and strict mapping functions. data Solo a MkSolo :: a -> Solo a pattern Solo :: a -> Solo a -- | Extract the value from a Solo. Very often, values should be -- extracted directly using pattern matching, to control just what gets -- evaluated when. getSolo is for convenience in situations -- where that is not the case: -- -- When the result is passed to a strict function, it makes no -- difference whether the pattern matching is done on the "outside" or on -- the "inside": -- --
--   Data.Set.insert (getSolo sol) set === case sol of Solo v -> Data.Set.insert v set
--   
-- -- A traversal may be performed in Solo in order to control -- evaluation internally, while using getSolo to extract the -- final result. A strict mapping function, for example, could be defined -- --
--   map' :: Traversable t => (a -> b) -> t a -> t b
--   map' f = getSolo . traverse ((Solo $!) . f)
--   
getSolo :: Solo a -> a -- | 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. -- --

Examples

-- --
--   >>> curry fst 1 2
--   1
--   
curry :: ((a, b) -> c) -> a -> b -> c -- | uncurry converts a curried function to a function on pairs. -- --

Examples

-- --
--   >>> uncurry (+) (1,2)
--   3
--   
-- --
--   >>> uncurry ($) (show, 1)
--   "1"
--   
-- --
--   >>> map (uncurry max) [(1,2), (3,4), (6,8)]
--   [2,4,8]
--   
uncurry :: (a -> b -> c) -> (a, b) -> c -- | Swap the components of a pair. swap :: (a, b) -> (b, a) -- | A type f is a Functor if it provides a function fmap -- which, given any types a and b, lets you apply any -- function of type (a -> b) to turn an f a into an -- f b, preserving the structure of f. -- --

Examples

-- --
--   >>> fmap show (Just 1)  --  (a   -> b)      -> f a       -> f b
--   Just "1"                --  (Int -> String) -> Maybe Int -> Maybe String
--   
-- --
--   >>> fmap show Nothing   --  (a   -> b)      -> f a       -> f b
--   Nothing                 --  (Int -> String) -> Maybe Int -> Maybe String
--   
-- --
--   >>> fmap show [1,2,3]   --  (a   -> b)      -> f a       -> f b
--   ["1","2","3"]           --  (Int -> String) -> [Int]     -> [String]
--   
-- --
--   >>> fmap show []        --  (a   -> b)      -> f a       -> f b
--   []                      --  (Int -> String) -> [Int]     -> [String]
--   
-- -- The fmap function is also available as the infix operator -- <$>: -- --
--   >>> fmap show (Just 1) --  (Int -> String) -> Maybe Int -> Maybe String
--   Just "1"
--   
--   >>> show <$> (Just 1)  --  (Int -> String) -> Maybe Int -> Maybe String
--   Just "1"
--   
module Data.Functor -- | A type f is a Functor if it provides a function fmap -- which, given any types a and b lets you apply any -- function from (a -> b) to turn an f a into an -- f b, preserving the structure of f. Furthermore -- f needs to adhere to the following: -- -- -- -- Note, that the second law follows from the free theorem of the type -- fmap and the first law, so you need only check that the former -- condition holds. See -- https://www.schoolofhaskell.com/user/edwardk/snippets/fmap or -- https://github.com/quchen/articles/blob/master/second_functor_law.md -- for an explanation. class Functor (f :: Type -> Type) -- | fmap is used to apply a function of type (a -> b) -- to a value of type f a, where f is a functor, to produce a -- value of type f b. Note that for any type constructor with -- more than one parameter (e.g., Either), only the last type -- parameter can be modified with fmap (e.g., b in -- `Either a b`). -- -- Some type constructors with two parameters or more have a -- Bifunctor instance that allows both the last and the -- penultimate parameters to be mapped over. -- --

Examples

-- -- Convert from a Maybe Int to a Maybe String -- using show: -- --
--   >>> fmap show Nothing
--   Nothing
--   
--   >>> fmap show (Just 3)
--   Just "3"
--   
-- -- Convert from an Either Int Int to an Either Int -- String using show: -- --
--   >>> fmap show (Left 17)
--   Left 17
--   
--   >>> fmap show (Right 17)
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> fmap (*2) [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> fmap even (2,2)
--   (2,True)
--   
-- -- It may seem surprising that the function is only applied to the last -- element of the tuple compared to the list example above which applies -- it to every element in the list. To understand, remember that tuples -- are type constructors with multiple type parameters: a tuple of 3 -- elements (a,b,c) can also be written (,,) a b c and -- its Functor instance is defined for Functor ((,,) a -- b) (i.e., only the third parameter is free to be mapped over with -- fmap). -- -- It explains why fmap can be used with tuples containing -- values of different types as in the following example: -- --
--   >>> fmap even ("hello", 1.0, 4)
--   ("hello",1.0,True)
--   
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. -- --

Examples

-- -- Perform a computation with Maybe and replace the result with a -- constant value if it is Just: -- --
--   >>> 'a' <$ Just 2
--   Just 'a'
--   
--   >>> 'a' <$ Nothing
--   Nothing
--   
(<$) :: 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 <$> -- | Flipped version of <$>. -- --
--   (<&>) = flip fmap
--   
-- --

Examples

-- -- Apply (+1) to a list, a Just and a Right: -- --
--   >>> Just 2 <&> (+1)
--   Just 3
--   
-- --
--   >>> [1,2,3] <&> (+1)
--   [2,3,4]
--   
-- --
--   >>> Right 3 <&> (+1)
--   Right 4
--   
(<&>) :: Functor f => f a -> (a -> b) -> f b infixl 1 <&> -- | Generalization of Data.List.unzip. unzip :: Functor f => f (a, b) -> (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 () -- | 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. -- -- The Haskell Report defines no laws for Eq. However, instances -- are encouraged to follow these properties: -- -- -- -- Minimal complete definition: either == or /=. class Eq a (==) :: Eq a => a -> a -> Bool (/=) :: Eq a => a -> a -> Bool infix 4 == infix 4 /= -- | 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. -- -- When used in conversions involving a newtype wrapper, make sure the -- newtype constructor is in scope. -- -- This function is representation-polymorphic, but the -- RuntimeRep type argument is marked as Inferred, -- meaning that it is not available for visible type application. This -- means the typechecker will accept coerce @Int @Age -- 42. -- --

Examples

-- --
--   >>> newtype TTL = TTL Int deriving (Eq, Ord, Show)
--   
--   >>> newtype Age = Age Int deriving (Eq, Ord, Show)
--   
--   >>> coerce (Age 42) :: TTL
--   TTL 42
--   
--   >>> coerce (+ (1 :: Int)) (Age 42) :: TTL
--   TTL 43
--   
--   >>> coerce (map (+ (1 :: Int))) [Age 42, Age 24] :: [TTL]
--   [TTL 43,TTL 25]
--   
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 a ~R# b => Coercible (a :: k) (b :: k) -- | The Bool type and related functions. module Data.Bool data Bool False :: Bool True :: Bool -- | Boolean "and", lazy in the second argument (&&) :: Bool -> Bool -> Bool infixr 3 && -- | Boolean "or", lazy in the second argument (||) :: 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 family If (cond :: Bool) (tru :: k) (fls :: k) :: k -- | Type-level "and" type family (a :: Bool) && (b :: Bool) :: Bool infixr 3 && -- | Type-level "or" type family (a :: Bool) || (b :: Bool) :: Bool infixr 2 || -- | Type-level "not". An injective type family since 4.10.0.0. type family Not (a :: Bool) = (res :: Bool) | res -> a -- | Simple combinators working solely on and with functions. module Data.Function -- | Identity function. -- --
--   id x = x
--   
-- -- This function might seem useless at first glance, but it can be very -- useful in a higher order context. -- --

Examples

-- --
--   >>> length $ filter id [True, True, False, True]
--   3
--   
-- --
--   >>> Just (Just 3) >>= id
--   Just 3
--   
-- --
--   >>> foldr id 0 [(^3), (*5), (+2)]
--   1000
--   
id :: a -> a -- | const x y always evaluates to x, ignoring its second -- argument. -- --
--   const x = \_ -> x
--   
-- -- This function might seem useless at first glance, but it can be very -- useful in a higher order context. -- --

Examples

-- --
--   >>> const 42 "hello"
--   42
--   
-- --
--   >>> map (const 42) [0..3]
--   [42,42,42,42]
--   
const :: a -> b -> a -- | Right to left function composition. -- --
--   (f . g) x = f (g x)
--   
-- --
--   f . id = f = id . f
--   
-- --

Examples

-- --
--   >>> map ((*2) . length) [[], [0, 1, 2], [0]]
--   [0,6,2]
--   
-- --
--   >>> foldr (.) id [(+1), (*3), (^3)] 2
--   25
--   
-- --
--   >>> let (...) = (.).(.) in ((*2)...(+)) 5 10
--   30
--   
(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | flip f takes its (first) two arguments in the reverse -- order of f. -- --
--   flip f x y = f y x
--   
-- --
--   flip . flip = id
--   
-- --

Examples

-- --
--   >>> flip (++) "hello" "world"
--   "worldhello"
--   
-- --
--   >>> let (.>) = flip (.) in (+1) .> show $ 5
--   "6"
--   
flip :: (a -> b -> c) -> b -> a -> c -- | ($) is the function application operator. -- -- Applying ($) to a function f and an argument -- x gives the same result as applying f to x -- directly. The definition is akin to this: -- --
--   ($) :: (a -> b) -> a -> b
--   ($) f x = f x
--   
-- -- This is id specialized from a -> a to -- (a -> b) -> (a -> b) which by the associativity of -- (->) is the same as (a -> b) -> a -> b. -- -- On the face of it, this may appear pointless! But it's actually one of -- the most useful and important operators in Haskell. -- -- The order of operations is very different between ($) and -- normal function application. Normal function application has -- precedence 10 - higher than any operator - and associates to the left. -- So these two definitions are equivalent: -- --
--   expr = min 5 1 + 5
--   expr = ((min 5) 1) + 5
--   
-- -- ($) has precedence 0 (the lowest) and associates to the -- right, so these are equivalent: -- --
--   expr = min 5 $ 1 + 5
--   expr = (min 5) (1 + 5)
--   
-- --

Examples

-- -- A common use cases of ($) is to avoid parentheses in complex -- expressions. -- -- For example, instead of using nested parentheses in the following -- Haskell function: -- --
--   -- | Sum numbers in a string: strSum "100  5 -7" == 98
--   strSum :: String -> Int
--   strSum s = sum (mapMaybe readMaybe (words s))
--   
-- -- we can deploy the function application operator: -- --
--   -- | Sum numbers in a string: strSum "100  5 -7" == 98
--   strSum :: String -> Int
--   strSum s = sum $ mapMaybe readMaybe $ words s
--   
-- -- ($) is also used as a section (a partially applied operator), -- in order to indicate that we wish to apply some yet-unspecified -- function to a given value. For example, to apply the argument -- 5 to a list of functions: -- --
--   applyFive :: [Int]
--   applyFive = map ($ 5) [(+1), (2^)]
--   >>> [6, 32]
--   
-- --

Technical Remark (Representation Polymorphism)

-- -- ($) is fully representation-polymorphic. This allows it to -- also be used with arguments of unlifted and even unboxed kinds, such -- as unboxed integers: -- --
--   fastMod :: Int -> Int -> Int
--   fastMod (I# x) (I# m) = I# $ remInt# x m
--   
($) :: forall (repa :: RuntimeRep) (repb :: RuntimeRep) (a :: TYPE repa) (b :: TYPE repb). (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 $. -- -- This is a version of flip id, where id -- is specialized from a -> a to (a -> b) -> (a -- -> b) which by the associativity of (->) is (a -- -> b) -> a -> b. flipping this yields a -> (a -- -> b) -> b which is the type signature of & -- --

Examples

-- --
--   >>> 5 & (+1) & show
--   "6"
--   
-- --
--   >>> sqrt $ [1 / n^2 | n <- [1..1000]] & sum & (*6)
--   3.1406380562059946
--   
(&) :: forall (r :: RuntimeRep) a (b :: TYPE r). 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. -- -- When f is strict, this means that because, by the definition -- of strictness, f ⊥ = ⊥ and such the least defined fixed point -- of any strict function is . -- --

Examples

-- -- We can write the factorial function using direct recursion as -- --
--   >>> let fac n = if n <= 1 then 1 else n * fac (n-1) in fac 5
--   120
--   
-- -- This uses the fact that Haskell’s let introduces recursive -- bindings. We can rewrite this definition using fix, -- -- Instead of making a recursive call, we introduce a dummy parameter -- rec; when used within fix, this parameter then refers -- to fix’s argument, hence the recursion is reintroduced. -- --
--   >>> fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5
--   120
--   
-- -- Using fix, we can implement versions of repeat as -- fix . (:) and cycle as -- fix . (++) -- --
--   >>> take 10 $ fix (0:)
--   [0,0,0,0,0,0,0,0,0,0]
--   
-- --
--   >>> map (fix (\rec n -> if n < 2 then n else rec (n - 1) + rec (n - 2))) [1..10]
--   [1,1,2,3,5,8,13,21,34,55]
--   
-- --

Implementation Details

-- -- The current implementation of fix uses structural sharing -- --
--   fix f = let x = f x in x
--   
-- -- A more straightforward but non-sharing version would look like -- --
--   fix f = f (fix f)
--   
fix :: (a -> a) -> a -- | on b u x y runs the binary function b -- on the results of applying unary function u to two -- arguments x and y. From the opposite perspective, it -- transforms two inputs and combines the outputs. -- --
--   (op `on` f) x y = f x `op` f y
--   
-- --

Examples

-- --
--   >>> sortBy (compare `on` length) [[0, 1, 2], [0, 1], [], [0]]
--   [[],[0],[0,1],[0,1,2]]
--   
-- --
--   >>> ((+) `on` length) [1, 2, 3] [-1]
--   4
--   
-- --
--   >>> ((,) `on` (*2)) 2 3
--   (4,6)
--   
-- --

Algebraic properties

-- -- -- -- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 `on` -- | applyWhen applies a function to a value if a condition is true, -- otherwise, it returns the value unchanged. -- -- It is equivalent to flip (bool id). -- --

Examples

-- --
--   >>> map (\x -> applyWhen (odd x) (*2) x) [1..10]
--   [2,2,6,4,10,6,14,8,18,10]
--   
-- --
--   >>> map (\x -> applyWhen (length x > 6) ((++ "...") . take 3) x) ["Hi!", "This is amazing", "Hope you're doing well today!", ":D"]
--   ["Hi!","Thi...","Hop...",":D"]
--   
-- --

Algebraic properties

-- -- -- -- applyWhen :: Bool -> (a -> a) -> a -> a -- | 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://gitlab.haskell.org/haskell/prime/-/wikis/libraries/proposals/monad-fail -- 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
--   
-- -- fail s should be an action that runs in the monad itself, not -- an exception (except in instances of MonadIO). In particular, -- fail should not be implemented in terms of error. class Monad m => MonadFail (m :: Type -> Type) fail :: MonadFail m => String -> m a instance Control.Monad.Fail.MonadFail GHC.Types.IO instance Control.Monad.Fail.MonadFail [] instance Control.Monad.Fail.MonadFail GHC.Maybe.Maybe -- | 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
--   ...
--   
-- -- WARNING: This function is partial. You can use case-matching instead. fromJust :: HasCallStack => Maybe a -> a -- | The fromMaybe function takes a default value and a Maybe -- value. If the Maybe is Nothing, it returns the default -- value; 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 given Just. -- --

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] -- | The List data type and its operations module GHC.List -- | The builtin list type, usually written in its non-prefix form -- [a]. -- -- In Haskell, lists are one of the most important data types as they are -- often used analogous to loops in imperative programming languages. -- These lists are singly linked, which makes it unsuited for operations -- that require <math> access. Instead, lists are intended to be -- traversed. -- -- Lists are constructed recursively using the right-associative -- cons-operator (:) :: a -> [a] -> [a], which prepends an -- element to a list, and the empty list []. -- --
--   (1 : 2 : 3 : []) == (1 : (2 : (3 : []))) == [1, 2, 3]
--   
-- -- Internally and in memory, all the above are represented like this, -- with arrows being pointers to locations in memory. -- --
--   ╭───┬───┬──╮   ╭───┬───┬──╮   ╭───┬───┬──╮   ╭────╮
--   │(:)│   │ ─┼──>│(:)│   │ ─┼──>│(:)│   │ ─┼──>│ [] │
--   ╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰────╯
--         v              v              v
--         1              2              3
--   
-- -- As seen above, lists can also be constructed using list literals of -- the form [x_1, x_2, ..., x_n] which are syntactic sugar and, -- unless -XOverloadedLists is enabled, are translated into uses -- of (:) and [] -- -- Similarly, String literals of the form "I 💜 hs" are -- translated into Lists of characters, ['I', ' ', '💜', ' ', 'h', -- 's']. -- --

Examples

-- --
--   >>> ['H', 'a', 's', 'k', 'e', 'l', 'l']
--   "Haskell"
--   
-- --
--   >>> 1 : [4, 1, 5, 9]
--   [1,4,1,5,9]
--   
-- --
--   >>> [] : [] : []
--   [[],[]]
--   
data [] 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 -- | foldr' is a variant of foldr that begins list reduction -- from the last element and evaluates the accumulator strictly as it -- unwinds the stack back to the beginning of the list. The input list -- must be finite, otherwise foldr' runs out of space -- (diverges). -- -- Note that if the function that combines the accumulated value with -- each element is strict in the accumulator, other than a possible -- improvement in the constant factor, you get the same <math> -- space cost as with just foldr. -- -- If you want a strict right fold in constant space, you need a -- structure that supports faster than <math> access to the -- right-most element, such as Seq from the containers -- package. -- -- Use of this function is a hint that the [] structure may be a -- poor fit for the task at hand. If the order in which the elements are -- combined is not important, use foldl' instead. -- --
--   >>> foldr' (+) [1..4]  -- Use foldl' instead!
--   10
--   
--   >>> foldr' (&&) [True, False, True, True] -- Use foldr instead!
--   False
--   
--   >>> foldr' (||) [False, False, True, True] -- Use foldr instead!
--   True
--   
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. Note that -- unlike foldr, the accumulated value must be of the same type as -- the list elements. -- --
--   >>> foldr1 (+) [1..4]
--   10
--   
--   >>> foldr1 (+) []
--   *** Exception: Prelude.foldr1: empty list
--   
--   >>> foldr1 (-) [1..4]
--   -2
--   
--   >>> foldr1 (&&) [True, False, True, True]
--   False
--   
--   >>> foldr1 (||) [False, False, True, True]
--   True
--   
--   >>> force $ foldr1 (+) [1..]
--   *** Exception: stack overflow
--   
foldr1 :: HasCallStack => (a -> a -> a) -> [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 (+) 0 [1..4]
--   10
--   
--   >>> foldl (+) 42 []
--   42
--   
--   >>> foldl (-) 100 [1..4]
--   90
--   
--   >>> foldl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   "dcbafoo"
--   
--   >>> foldl (+) 0 [1..]
--   * Hangs forever *
--   
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. Note that -- unlike foldl, the accumulated value must be of the same type as -- the list elements. -- --
--   >>> foldl1 (+) [1..4]
--   10
--   
--   >>> foldl1 (+) []
--   *** Exception: Prelude.foldl1: empty list
--   
--   >>> foldl1 (-) [1..4]
--   -8
--   
--   >>> foldl1 (&&) [True, False, True, True]
--   False
--   
--   >>> foldl1 (||) [False, False, True, True]
--   True
--   
--   >>> foldl1 (+) [1..]
--   * Hangs forever *
--   
foldl1 :: HasCallStack => (a -> a -> a) -> [a] -> a -- | <math>. Test whether a list is empty. -- --
--   >>> null []
--   True
--   
--   >>> null [1]
--   False
--   
--   >>> null [1..]
--   False
--   
null :: [a] -> Bool -- | <math>. 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 []
--   0
--   
--   >>> length ['a', 'b', 'c']
--   3
--   
--   >>> length [1..]
--   * Hangs forever *
--   
length :: [a] -> Int -- | 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. -- --

Examples

-- --
--   >>> 3 `elem` []
--   False
--   
-- --
--   >>> 3 `elem` [1,2]
--   False
--   
-- --
--   >>> 3 `elem` [1,2,3,4,5]
--   True
--   
-- --
--   >>> 3 `elem` [1..]
--   True
--   
-- --
--   >>> 3 `elem` [4..]
--   * Hangs forever *
--   
elem :: Eq a => a -> [a] -> Bool infix 4 `elem` -- | notElem is the negation of elem. -- --

Examples

-- --
--   >>> 3 `notElem` []
--   True
--   
-- --
--   >>> 3 `notElem` [1,2]
--   True
--   
-- --
--   >>> 3 `notElem` [1,2,3,4,5]
--   False
--   
-- --
--   >>> 3 `notElem` [1..]
--   False
--   
-- --
--   >>> 3 `notElem` [4..]
--   * Hangs forever *
--   
notElem :: Eq a => a -> [a] -> Bool infix 4 `notElem` -- | 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 []
--   *** Exception: Prelude.maximum: empty list
--   
--   >>> maximum [42]
--   42
--   
--   >>> maximum [55, -12, 7, 0, -89]
--   55
--   
--   >>> maximum [1..]
--   * Hangs forever *
--   
maximum :: (Ord a, HasCallStack) => [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 []
--   *** Exception: Prelude.minimum: empty list
--   
--   >>> minimum [42]
--   42
--   
--   >>> minimum [55, -12, 7, 0, -89]
--   -89
--   
--   >>> minimum [1..]
--   * Hangs forever *
--   
minimum :: (Ord a, HasCallStack) => [a] -> a -- | The sum function computes the sum of a finite list of numbers. -- --
--   >>> sum []
--   0
--   
--   >>> sum [42]
--   42
--   
--   >>> sum [1..10]
--   55
--   
--   >>> sum [4.1, 2.0, 1.7]
--   7.8
--   
--   >>> sum [1..]
--   * Hangs forever *
--   
sum :: Num a => [a] -> a -- | The product function computes the product of a finite list of -- numbers. -- --
--   >>> product []
--   1
--   
--   >>> product [42]
--   42
--   
--   >>> product [1..10]
--   3628800
--   
--   >>> product [4.1, 2.0, 1.7]
--   13.939999999999998
--   
--   >>> product [1..]
--   * Hangs forever *
--   
product :: Num a => [a] -> a -- | and returns the conjunction of a Boolean list. For the result -- to be True, the list must be finite; False, however, -- results from a False value at a finite index of a finite or -- infinite list. -- --

Examples

-- --
--   >>> and []
--   True
--   
-- --
--   >>> and [True]
--   True
--   
-- --
--   >>> and [False]
--   False
--   
-- --
--   >>> and [True, True, False]
--   False
--   
-- --
--   >>> and (False : repeat True) -- Infinite list [False,True,True,True,True,True,True...
--   False
--   
-- --
--   >>> and (repeat True)
--   * Hangs forever *
--   
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. -- --

Examples

-- --
--   >>> or []
--   False
--   
-- --
--   >>> or [True]
--   True
--   
-- --
--   >>> or [False]
--   False
--   
-- --
--   >>> or [True, True, False]
--   True
--   
-- --
--   >>> or (True : repeat False) -- Infinite list [True,False,False,False,False,False,False...
--   True
--   
-- --
--   >>> or (repeat False)
--   * Hangs forever *
--   
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. -- --

Examples

-- --
--   >>> any (> 3) []
--   False
--   
-- --
--   >>> any (> 3) [1,2]
--   False
--   
-- --
--   >>> any (> 3) [1,2,3,4,5]
--   True
--   
-- --
--   >>> any (> 3) [1..]
--   True
--   
-- --
--   >>> any (> 3) [0, -1..]
--   * Hangs forever *
--   
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. -- --

Examples

-- --
--   >>> all (> 3) []
--   True
--   
-- --
--   >>> all (> 3) [1,2]
--   False
--   
-- --
--   >>> all (> 3) [1,2,3,4,5]
--   False
--   
-- --
--   >>> all (> 3) [1..]
--   False
--   
-- --
--   >>> all (> 3) [4..]
--   * Hangs forever *
--   
all :: (a -> Bool) -> [a] -> Bool -- | A strict version of foldl1. foldl1' :: HasCallStack => (a -> a -> a) -> [a] -> a -- | Concatenate a list of lists. -- --

Examples

-- --
--   >>> concat [[1,2,3], [4,5], [6], []]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> concat []
--   []
--   
-- --
--   >>> concat [[42]]
--   [42]
--   
concat :: [[a]] -> [a] -- | Map a function returning a list over a list and concatenate the -- results. concatMap can be seen as the composition of -- concat and map. -- --
--   concatMap f xs == (concat . map f) xs
--   
-- --

Examples

-- --
--   >>> concatMap (\i -> [-i,i]) []
--   []
--   
-- --
--   >>> concatMap (\i -> [-i, i]) [1, 2, 3]
--   [-1,1,-2,2,-3,3]
--   
-- --
--   >>> concatMap ('replicate' 3) [0, 2, 4]
--   [0,0,0,2,2,2,4,4,4]
--   
concatMap :: (a -> [b]) -> [a] -> [b] -- | <math>. 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, ...]
--   
-- -- this means that map id == id -- --

Examples

-- --
--   >>> map (+1) [1, 2, 3]
--   [2,3,4]
--   
-- --
--   >>> map id [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> map (\n -> 3 * n + 1) [1, 2, 3]
--   [4,7,10]
--   
map :: (a -> b) -> [a] -> [b] -- | (++) appends 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. -- --

Performance considerations

-- -- This function takes linear time in the number of elements of the -- first list. Thus it is better to associate repeated -- applications of (++) to the right (which is the default -- behaviour): xs ++ (ys ++ zs) or simply xs ++ ys ++ -- zs, but not (xs ++ ys) ++ zs. For the same reason -- concat = foldr (++) [] has -- linear performance, while foldl (++) [] is -- prone to quadratic slowdown -- --

Examples

-- --
--   >>> [1, 2, 3] ++ [4, 5, 6]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> [] ++ [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> [3, 2, 1] ++ []
--   [3,2,1]
--   
(++) :: [a] -> [a] -> [a] infixr 5 ++ -- | <math>. 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]
--   
-- --

Examples

-- --
--   >>> filter odd [1, 2, 3]
--   [1,3]
--   
-- --
--   >>> filter (\l -> length l > 3) ["Hello", ", ", "World", "!"]
--   ["Hello","World"]
--   
-- --
--   >>> filter (/= 3) [1, 2, 3, 4, 3, 2, 1]
--   [1,2,4,2,1]
--   
filter :: (a -> Bool) -> [a] -> [a] -- | <math>. lookup key assocs looks up a key in an -- association list. For the result to be Nothing, the list must -- be finite. -- --

Examples

-- --
--   >>> lookup 2 []
--   Nothing
--   
-- --
--   >>> lookup 2 [(1, "first")]
--   Nothing
--   
-- --
--   >>> lookup 2 [(1, "first"), (2, "second"), (3, "third")]
--   Just "second"
--   
lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | <math>. Extract the first element of a list, which must be -- non-empty. -- --
Examples
-- --
--   >>> head [1, 2, 3]
--   1
--   
-- --
--   >>> head [1..]
--   1
--   
-- --
--   >>> head []
--   *** Exception: Prelude.head: empty list
--   
-- | Warning: This is a partial function, it throws an error on empty -- lists. Use pattern matching or Data.List.uncons instead. Consider -- refactoring to use Data.List.NonEmpty. head :: HasCallStack => [a] -> a -- | <math>. Extract the last element of a list, which must be finite -- and non-empty. -- -- WARNING: This function is partial. Consider using unsnoc -- instead. -- --

Examples

-- --
--   >>> last [1, 2, 3]
--   3
--   
-- --
--   >>> last [1..]
--   * Hangs forever *
--   
-- --
--   >>> last []
--   *** Exception: Prelude.last: empty list
--   
last :: HasCallStack => [a] -> a -- | <math>. Extract the elements after the head of a list, which -- must be non-empty. -- --

Examples

-- --
--   >>> tail [1, 2, 3]
--   [2,3]
--   
-- --
--   >>> tail [1]
--   []
--   
-- --
--   >>> tail []
--   *** Exception: Prelude.tail: empty list
--   
-- | Warning: This is a partial function, it throws an error on empty -- lists. Replace it with drop 1, or use pattern matching or -- Data.List.uncons instead. Consider refactoring to use -- Data.List.NonEmpty. tail :: HasCallStack => [a] -> [a] -- | <math>. Return all the elements of a list except the last one. -- The list must be non-empty. -- -- WARNING: This function is partial. Consider using unsnoc -- instead. -- --

Examples

-- --
--   >>> init [1, 2, 3]
--   [1,2]
--   
-- --
--   >>> init [1]
--   []
--   
-- --
--   >>> init []
--   *** Exception: Prelude.init: empty list
--   
init :: HasCallStack => [a] -> [a] -- | <math>. Decompose a list into its head and tail. -- -- -- --

Examples

-- --
--   >>> uncons []
--   Nothing
--   
-- --
--   >>> uncons [1]
--   Just (1,[])
--   
-- --
--   >>> uncons [1, 2, 3]
--   Just (1,[2,3])
--   
uncons :: [a] -> Maybe (a, [a]) -- | <math>. Decompose a list into init and last. -- -- -- -- unsnoc is dual to uncons: for a finite list xs -- --
--   unsnoc xs = (\(hd, tl) -> (reverse tl, hd)) <$> uncons (reverse xs)
--   
-- --

Examples

-- --
--   >>> unsnoc []
--   Nothing
--   
-- --
--   >>> unsnoc [1]
--   Just ([],1)
--   
-- --
--   >>> unsnoc [1, 2, 3]
--   Just ([1,2],3)
--   
-- --

Laziness

-- --
--   >>> fst <$> unsnoc [undefined]
--   Just []
--   
-- --
--   >>> head . fst <$> unsnoc (1 : undefined)
--   Just *** Exception: Prelude.undefined
--   
-- --
--   >>> head . fst <$> unsnoc (1 : 2 : undefined)
--   Just 1
--   
unsnoc :: [a] -> Maybe ([a], a) -- | List index (subscript) operator, starting from 0. Returns -- Nothing if the index is out of bounds -- -- This is the total variant of the partial !! operator. -- -- WARNING: This function takes linear time in the index. -- --

Examples

-- --
--   >>> ['a', 'b', 'c'] !? 0
--   Just 'a'
--   
-- --
--   >>> ['a', 'b', 'c'] !? 2
--   Just 'c'
--   
-- --
--   >>> ['a', 'b', 'c'] !? 3
--   Nothing
--   
-- --
--   >>> ['a', 'b', 'c'] !? (-1)
--   Nothing
--   
(!?) :: [a] -> Int -> Maybe a infixl 9 !? -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. -- -- WARNING: This function is partial, and should only be used if you are -- sure that the indexing will not fail. Otherwise, use !?. -- -- WARNING: This function takes linear time in the index. -- --

Examples

-- --
--   >>> ['a', 'b', 'c'] !! 0
--   'a'
--   
-- --
--   >>> ['a', 'b', 'c'] !! 2
--   'c'
--   
-- --
--   >>> ['a', 'b', 'c'] !! 3
--   *** Exception: Prelude.!!: index too large
--   
-- --
--   >>> ['a', 'b', 'c'] !! (-1)
--   *** Exception: Prelude.!!: negative index
--   
(!!) :: HasCallStack => [a] -> Int -> a infixl 9 !! -- | <math>. 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
--   
-- --

Examples

-- --
--   >>> scanl (+) 0 [1..4]
--   [0,1,3,6,10]
--   
-- --
--   >>> scanl (+) 42 []
--   [42]
--   
-- --
--   >>> scanl (-) 100 [1..4]
--   [100,99,97,94,90]
--   
-- --
--   >>> scanl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   ["foo","afoo","bafoo","cbafoo","dcbafoo"]
--   
-- --
--   >>> take 10 (scanl (+) 0 [1..])
--   [0,1,3,6,10,15,21,28,36,45]
--   
-- --
--   >>> take 1 (scanl undefined 'a' undefined)
--   "a"
--   
scanl :: (b -> a -> b) -> b -> [a] -> [b] -- | <math>. scanl1 is a variant of scanl that has no -- starting value argument: -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
-- --

Examples

-- --
--   >>> scanl1 (+) [1..4]
--   [1,3,6,10]
--   
-- --
--   >>> scanl1 (+) []
--   []
--   
-- --
--   >>> scanl1 (-) [1..4]
--   [1,-1,-4,-8]
--   
-- --
--   >>> scanl1 (&&) [True, False, True, True]
--   [True,False,False,False]
--   
-- --
--   >>> scanl1 (||) [False, False, True, True]
--   [False,False,True,True]
--   
-- --
--   >>> take 10 (scanl1 (+) [1..])
--   [1,3,6,10,15,21,28,36,45,55]
--   
-- --
--   >>> take 1 (scanl1 undefined ('a' : undefined))
--   "a"
--   
scanl1 :: (a -> a -> a) -> [a] -> [a] -- | <math>. A strict version of scanl. scanl' :: (b -> a -> b) -> b -> [a] -> [b] -- | <math>. scanr is the right-to-left dual of scanl. -- Note that the order of parameters on the accumulating function are -- reversed compared to scanl. Also note that -- --
--   head (scanr f z xs) == foldr f z xs.
--   
-- --

Examples

-- --
--   >>> scanr (+) 0 [1..4]
--   [10,9,7,4,0]
--   
-- --
--   >>> scanr (+) 42 []
--   [42]
--   
-- --
--   >>> scanr (-) 100 [1..4]
--   [98,-97,99,-96,100]
--   
-- --
--   >>> scanr (\nextChar reversedString -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   ["abcdfoo","bcdfoo","cdfoo","dfoo","foo"]
--   
-- --
--   >>> force $ scanr (+) 0 [1..]
--   *** Exception: stack overflow
--   
scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | <math>. scanr1 is a variant of scanr that has no -- starting value argument. -- --

Examples

-- --
--   >>> scanr1 (+) [1..4]
--   [10,9,7,4]
--   
-- --
--   >>> scanr1 (+) []
--   []
--   
-- --
--   >>> scanr1 (-) [1..4]
--   [-2,3,-1,4]
--   
-- --
--   >>> scanr1 (&&) [True, False, True, True]
--   [False,False,True,True]
--   
-- --
--   >>> scanr1 (||) [True, True, False, False]
--   [True,True,False,False]
--   
-- --
--   >>> force $ scanr1 (+) [1..]
--   *** Exception: stack overflow
--   
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), ...]
--   
-- --

Laziness

-- -- Note that iterate is lazy, potentially leading to thunk -- build-up if the consumer doesn't force each iterate. See -- iterate' for a strict variant of this function. -- --
--   >>> take 1 $ iterate undefined 42
--   [42]
--   
-- --

Examples

-- --
--   >>> take 10 $ iterate not True
--   [True,False,True,False,True,False,True,False,True,False]
--   
-- --
--   >>> take 10 $ iterate (+3) 42
--   [42,45,48,51,54,57,60,63,66,69]
--   
-- -- iterate id == repeat: -- --
--   >>> take 10 $ iterate id 1
--   [1,1,1,1,1,1,1,1,1,1]
--   
iterate :: (a -> a) -> a -> [a] -- | iterate' is the strict version of iterate. -- -- It forces the result of each application of the function to weak head -- normal form (WHNF) before proceeding. -- --
--   >>> take 1 $ iterate' undefined 42
--   *** Exception: Prelude.undefined
--   
iterate' :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. -- --

Examples

-- --
--   >>> take 10 $ repeat 17
--   [17,17,17,17,17,17,17,17,17, 17]
--   
-- --
--   >>> repeat undefined
--   [*** Exception: Prelude.undefined
--   
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. -- --

Examples

-- --
--   >>> replicate 0 True
--   []
--   
-- --
--   >>> replicate (-1) True
--   []
--   
-- --
--   >>> replicate 4 True
--   [True,True,True,True]
--   
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. -- --

Examples

-- --
--   >>> cycle []
--   *** Exception: Prelude.cycle: empty list
--   
-- --
--   >>> take 10 (cycle [42])
--   [42,42,42,42,42,42,42,42,42,42]
--   
-- --
--   >>> take 10 (cycle [2, 5, 7])
--   [2,5,7,2,5,7,2,5,7,2]
--   
-- --
--   >>> take 1 (cycle (42 : undefined))
--   [42]
--   
cycle :: HasCallStack => [a] -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n >= length xs. -- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. -- --

Laziness

-- --
--   >>> take 0 undefined
--   []
--   
--   >>> take 2 (1 : 2 : undefined)
--   [1,2]
--   
-- --

Examples

-- --
--   >>> 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]
--   []
--   
take :: Int -> [a] -> [a] -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n >= length -- xs. -- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. -- --

Examples

-- --
--   >>> 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]
--   
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 is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. -- --

Laziness

-- -- It is equivalent to (take n xs, drop n xs) -- unless n is _|_: splitAt _|_ xs = _|_, not -- (_|_, _|_)). -- -- The first component of the tuple is produced lazily: -- --
--   >>> fst (splitAt 0 undefined)
--   []
--   
-- --
--   >>> take 1 (fst (splitAt 10 (1 : undefined)))
--   [1]
--   
-- --

Examples

-- --
--   >>> 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])
--   
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. -- --

Laziness

-- --
--   >>> takeWhile (const False) undefined
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> takeWhile (const False) (undefined : undefined)
--   []
--   
-- --
--   >>> take 1 (takeWhile (const True) (1 : undefined))
--   [1]
--   
-- --

Examples

-- --
--   >>> 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. -- --

Examples

-- --
--   >>> 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 the longest prefix (possibly -- empty) of xs of elements that satisfy p and second -- element is the remainder of the list: -- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs), even if p is _|_. -- --

Laziness

-- --
--   >>> span undefined []
--   ([],[])
--   
--   >>> fst (span (const False) undefined)
--   *** Exception: Prelude.undefined
--   
--   >>> fst (span (const False) (undefined : undefined))
--   []
--   
--   >>> take 1 (fst (span (const True) (1 : undefined)))
--   [1]
--   
-- -- span produces the first component of the tuple lazily: -- --
--   >>> take 10 (fst (span (const True) [1..]))
--   [1,2,3,4,5,6,7,8,9,10]
--   
-- --

Examples

-- --
--   >>> 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 :: (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 p is equivalent to span (not . -- p) and consequently to (takeWhile (not . p) xs, -- dropWhile (not . p) xs), even if p is -- _|_. -- --

Laziness

-- --
--   >>> break undefined []
--   ([],[])
--   
-- --
--   >>> fst (break (const True) undefined)
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> fst (break (const True) (undefined : undefined))
--   []
--   
-- --
--   >>> take 1 (fst (break (const False) (1 : undefined)))
--   [1]
--   
-- -- break produces the first component of the tuple lazily: -- --
--   >>> take 10 (fst (break (const False) [1..]))
--   [1,2,3,4,5,6,7,8,9,10]
--   
-- --

Examples

-- --
--   >>> 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 :: (a -> Bool) -> [a] -> ([a], [a]) -- | <math>. reverse xs returns the elements of -- xs in reverse order. xs must be finite. -- --

Laziness

-- -- reverse is lazy in its elements. -- --
--   >>> head (reverse [undefined, 1])
--   1
--   
-- --
--   >>> reverse (1 : 2 : undefined)
--   *** Exception: Prelude.undefined
--   
-- --

Examples

-- --
--   >>> reverse []
--   []
--   
-- --
--   >>> reverse [42]
--   [42]
--   
-- --
--   >>> reverse [2,5,7]
--   [7,5,2]
--   
-- --
--   >>> reverse [1..]
--   * Hangs forever *
--   
reverse :: [a] -> [a] -- | <math>. zip takes two lists and returns a list of -- corresponding pairs. -- -- zip is right-lazy: -- --
--   >>> zip [] undefined
--   []
--   
--   >>> zip undefined []
--   *** Exception: Prelude.undefined
--   ...
--   
-- -- zip is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. -- --

Examples

-- --
--   >>> zip [1, 2, 3] ['a', 'b', 'c']
--   [(1,'a'),(2,'b'),(3,'c')]
--   
-- -- If one input list is shorter than the other, excess elements of the -- longer list are discarded, even if one of the lists is infinite: -- --
--   >>> zip [1] ['a', 'b']
--   [(1,'a')]
--   
-- --
--   >>> zip [1, 2] ['a']
--   [(1,'a')]
--   
-- --
--   >>> zip [] [1..]
--   []
--   
-- --
--   >>> zip [1..] []
--   []
--   
zip :: [a] -> [b] -> [(a, b)] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. It is capable of list fusion, but it is restricted to -- its first list argument and its resulting list. zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] -- | <math>. zipWith generalises zip by zipping with -- the function given as the first argument, instead of a tupling -- function. -- --
--   zipWith (,) xs ys == zip xs ys
--   zipWith f [x1,x2,x3..] [y1,y2,y3..] == [f x1 y1, f x2 y2, f x3 y3..]
--   
-- -- zipWith is right-lazy: -- --
--   >>> let f = undefined
--   
--   >>> zipWith f [] undefined
--   []
--   
-- -- zipWith is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. -- --

Examples

-- -- zipWith (+) can be applied to two lists to -- produce the list of corresponding sums: -- --
--   >>> zipWith (+) [1, 2, 3] [4, 5, 6]
--   [5,7,9]
--   
-- --
--   >>> zipWith (++) ["hello ", "foo"] ["world!", "bar"]
--   ["hello world!","foobar"]
--   
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | <math>. The zipWith3 function takes a function which -- combines three elements, as well as three lists and returns a list of -- the function applied to corresponding elements, analogous to -- zipWith. It is capable of list fusion, but it is restricted to -- its first list argument and its resulting list. -- --
--   zipWith3 (,,) xs ys zs == zip3 xs ys zs
--   zipWith3 f [x1,x2,x3..] [y1,y2,y3..] [z1,z2,z3..] == [f x1 y1 z1, f x2 y2 z2, f x3 y3 z3..]
--   
-- --

Examples

-- --
--   >>> zipWith3 (\x y z -> [x, y, z]) "123" "abc" "xyz"
--   ["1ax","2by","3cz"]
--   
-- --
--   >>> zipWith3 (\x y z -> (x * y) + z) [1, 2, 3] [4, 5, 6] [7, 8, 9]
--   [11,18,27]
--   
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. -- --

Examples

-- --
--   >>> unzip []
--   ([],[])
--   
-- --
--   >>> unzip [(1, 'a'), (2, 'b')]
--   ([1,2],"ab")
--   
unzip :: [(a, b)] -> ([a], [b]) -- | The unzip3 function takes a list of triples and returns three -- lists of the respective components, analogous to unzip. -- --

Examples

-- --
--   >>> unzip3 []
--   ([],[],[])
--   
-- --
--   >>> unzip3 [(1, 'a', True), (2, 'b', False)]
--   ([1,2],"ab",[True,False])
--   
unzip3 :: [(a, b, c)] -> ([a], [b], [c]) errorEmptyList :: HasCallStack => String -> a -- | A list producer that can be fused with foldr. This function is -- merely -- --
--   augment g xs = g (:) xs
--   
-- -- but GHC's simplifier will transform an expression of the form -- foldr k z (augment g xs), which may arise after -- inlining, to g k (foldr k z xs), which avoids -- producing an intermediate list. augment :: (forall b. () => (a -> b -> b) -> b -> b) -> [a] -> [a] -- | A list producer that can be fused with foldr. This function is -- merely -- --
--   build g = g (:) []
--   
-- -- but GHC's simplifier will transform an expression of the form -- foldr k z (build g), which may arise after -- inlining, to g k z, which avoids producing an intermediate -- list. build :: (forall b. () => (a -> b -> b) -> b -> b) -> [a] -- | The Show class, and related operations. module GHC.Show -- | 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 -- | 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 -- | 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 -- | Like showLitString (expand escape characters using Haskell -- escape conventions), but * break the string into multiple lines * wrap -- the entire thing in double quotes Example: showMultiLineString -- "hellongoodbyenblah" returns [""hello\n\", "\goodbyen\", -- "\blah""] showMultiLineString :: String -> [String] -- | utility function that surrounds the inner show function with -- parentheses when the Bool parameter is True. showParen :: Bool -> ShowS -> ShowS showList__ :: (a -> ShowS) -> [a] -> ShowS showCommaSpace :: ShowS showSpace :: ShowS -- | 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 -- | Same as showLitChar, but for strings It converts the string to -- a string using Haskell escape conventions for non-printable -- characters. Does not add double-quotes around the whole thing; the -- caller should do that. The main difference from showLitChar (apart -- from the fact that the argument is a string not a list) is that we -- must escape double-quotes showLitString :: String -> ShowS protectEsc :: (Char -> Bool) -> ShowS -> ShowS -- | 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 showSignedInt :: Int -> Int -> ShowS appPrec :: Int appPrec1 :: Int asciiTab :: [String] instance GHC.Show.Show GHC.Types.Bool instance GHC.Show.Show GHC.Stack.Types.CallStack instance GHC.Show.Show GHC.Types.Char instance GHC.Show.Show GHC.Types.Int instance GHC.Show.Show GHC.Num.Integer.Integer instance GHC.Show.Show GHC.Types.KindRep instance GHC.Show.Show GHC.Types.Levity instance GHC.Show.Show a => GHC.Show.Show [a] instance GHC.Show.Show a => GHC.Show.Show (GHC.Maybe.Maybe a) instance GHC.Show.Show GHC.Types.Module instance GHC.Show.Show GHC.Num.Natural.Natural instance GHC.Show.Show a => GHC.Show.Show (GHC.Base.NonEmpty a) instance GHC.Show.Show GHC.Types.Ordering instance GHC.Show.Show GHC.Types.RuntimeRep instance GHC.Show.Show a => GHC.Show.Show (GHC.Tuple.Prim.Solo a) instance GHC.Show.Show GHC.Stack.Types.SrcLoc instance GHC.Show.Show GHC.Types.TrName instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f, GHC.Show.Show g, GHC.Show.Show h, GHC.Show.Show i, GHC.Show.Show j) => GHC.Show.Show (a, b, c, d, e, f, g, h, i, j) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f, GHC.Show.Show g, GHC.Show.Show h, GHC.Show.Show i, GHC.Show.Show j, GHC.Show.Show k) => GHC.Show.Show (a, b, c, d, e, f, g, h, i, j, k) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f, GHC.Show.Show g, GHC.Show.Show h, GHC.Show.Show i, GHC.Show.Show j, GHC.Show.Show k, GHC.Show.Show l) => GHC.Show.Show (a, b, c, d, e, f, g, h, i, j, k, l) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f, GHC.Show.Show g, GHC.Show.Show h, GHC.Show.Show i, GHC.Show.Show j, GHC.Show.Show k, GHC.Show.Show l, GHC.Show.Show m) => GHC.Show.Show (a, b, c, d, e, f, g, h, i, j, k, l, m) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f, GHC.Show.Show g, GHC.Show.Show h, GHC.Show.Show i, GHC.Show.Show j, GHC.Show.Show k, GHC.Show.Show l, GHC.Show.Show m, GHC.Show.Show n) => GHC.Show.Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f, GHC.Show.Show g, GHC.Show.Show h, GHC.Show.Show i, GHC.Show.Show j, GHC.Show.Show k, GHC.Show.Show l, GHC.Show.Show m, GHC.Show.Show n, GHC.Show.Show o) => GHC.Show.Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (a, b) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c) => GHC.Show.Show (a, b, c) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d) => GHC.Show.Show (a, b, c, d) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e) => GHC.Show.Show (a, b, c, d, e) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f) => GHC.Show.Show (a, b, c, d, e, f) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f, GHC.Show.Show g) => GHC.Show.Show (a, b, c, d, e, f, g) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f, GHC.Show.Show g, GHC.Show.Show h) => GHC.Show.Show (a, b, c, d, e, f, g, h) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d, GHC.Show.Show e, GHC.Show.Show f, GHC.Show.Show g, GHC.Show.Show h, GHC.Show.Show i) => GHC.Show.Show (a, b, c, d, e, f, g, h, i) instance GHC.Show.Show GHC.Types.TyCon instance GHC.Show.Show GHC.Types.TypeLitSort instance GHC.Show.Show () instance GHC.Show.Show GHC.Types.VecCount instance GHC.Show.Show GHC.Types.VecElem instance GHC.Show.Show GHC.Base.Void instance GHC.Show.Show GHC.Types.Word -- | The ST Monad. module GHC.ST -- | The strict ST monad. The ST monad allows for destructive -- updates, but is escapable (unlike IO). A computation of type -- ST s a returns a value of type a, and execute -- in "thread" s. 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) = _|_
--   
newtype ST s a ST :: STRep s a -> ST s a data STret s a STret :: State# s -> a -> STret s a type STRep s a = State# s -> (# State# s, a #) -- | Return the value computed by a state thread. 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 liftST :: ST s a -> State# s -> STret s a -- | 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 instance GHC.Base.Applicative (GHC.ST.ST s) instance GHC.Base.Functor (GHC.ST.ST s) instance GHC.Base.Monad (GHC.ST.ST s) instance GHC.Base.Monoid a => GHC.Base.Monoid (GHC.ST.ST s a) instance GHC.Base.Semigroup a => GHC.Base.Semigroup (GHC.ST.ST s a) instance GHC.Show.Show (GHC.ST.ST s a) -- | References in the ST monad. module GHC.STRef -- | a value of type STRef s a is a mutable variable in state -- thread s, containing a value of type a -- --
--   >>> :{
--   runST (do
--       ref <- newSTRef "hello"
--       x <- readSTRef ref
--       writeSTRef ref (x ++ "world")
--       readSTRef ref )
--   :}
--   "helloworld"
--   
data STRef s a STRef :: MutVar# s a -> 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 () instance GHC.Classes.Eq (GHC.STRef.STRef s a) module GHC.Char -- | The toEnum method restricted to the type Char. chr :: Int -> Char eqChar :: Char -> Char -> Bool neChar :: Char -> Char -> Bool -- | The Enum and Bounded classes. module GHC.Enum -- | 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 :: Bounded a => a maxBound :: Bounded 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..] with [n..] = -- enumFrom n, a possible implementation being enumFrom n = n : -- enumFrom (succ n). For example: -- -- enumFrom :: Enum a => a -> [a] -- | Used in Haskell's translation of [n,n'..] with [n,n'..] = -- enumFromThen n n', a possible implementation being -- enumFromThen n n' = n : n' : worker (f x) (f x n'), -- worker s v = v : worker s (s v), x = fromEnum n' - -- fromEnum n and f n y | n > 0 = f (n - 1) (succ y) | n < -- 0 = f (n + 1) (pred y) | otherwise = y For example: -- -- enumFromThen :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n..m] with [n..m] = -- enumFromTo n m, a possible implementation being enumFromTo n -- m | n <= m = n : enumFromTo (succ n) m | otherwise = []. For -- example: -- -- enumFromTo :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n,n'..m] with [n,n'..m] -- = enumFromThenTo n n' m, a possible implementation being -- enumFromThenTo n n' m = worker (f x) (c x) n m, x = -- fromEnum n' - fromEnum n, c x = bool (>=) ((x -- 0) f n y | n > 0 = f (n - 1) (succ y) | n < 0 = f (n + -- 1) (pred y) | otherwise = y and worker s c v m | c v m = v : -- worker s c (s v) m | otherwise = [] For example: -- -- enumFromThenTo :: Enum a => a -> a -> a -> [a] boundedEnumFrom :: (Enum a, Bounded a) => a -> [a] boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a] toEnumError :: Show a => String -> Int -> (a, a) -> b fromEnumError :: Show a => String -> a -> b succError :: String -> a predError :: String -> a instance GHC.Enum.Bounded GHC.Types.Bool instance GHC.Enum.Bounded GHC.Types.Char instance GHC.Enum.Bounded GHC.Types.Int instance GHC.Enum.Bounded GHC.Types.Levity instance GHC.Enum.Bounded GHC.Types.Ordering instance GHC.Enum.Bounded a => GHC.Enum.Bounded (GHC.Tuple.Prim.Solo a) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n, GHC.Enum.Bounded o) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b) => GHC.Enum.Bounded (a, b) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c) => GHC.Enum.Bounded (a, b, c) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d) => GHC.Enum.Bounded (a, b, c, d) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e) => GHC.Enum.Bounded (a, b, c, d, e) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f) => GHC.Enum.Bounded (a, b, c, d, e, f) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g) => GHC.Enum.Bounded (a, b, c, d, e, f, g) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h) instance (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i) instance GHC.Enum.Bounded () instance GHC.Enum.Bounded GHC.Types.VecCount instance GHC.Enum.Bounded GHC.Types.VecElem instance GHC.Enum.Bounded GHC.Types.Word instance GHC.Enum.Enum GHC.Types.Bool instance GHC.Enum.Enum GHC.Types.Char instance GHC.Enum.Enum GHC.Types.Int instance GHC.Enum.Enum GHC.Num.Integer.Integer instance GHC.Enum.Enum GHC.Types.Levity instance GHC.Enum.Enum GHC.Num.Natural.Natural instance GHC.Enum.Enum GHC.Types.Ordering instance GHC.Enum.Enum a => GHC.Enum.Enum (GHC.Tuple.Prim.Solo a) instance GHC.Enum.Enum () instance GHC.Enum.Enum GHC.Types.VecCount instance GHC.Enum.Enum GHC.Types.VecElem instance GHC.Enum.Enum GHC.Types.Word -- | The types Ratio and Rational, and the classes -- Real, Fractional, Integral, and RealFrac. module GHC.Real divZeroError :: a ratioZeroDenominatorError :: a overflowError :: a underflowError :: a -- | Rational numbers, with numerator and denominator of some -- Integral type. -- -- Note that Ratio's instances inherit the deficiencies from the -- type parameter's. For example, Ratio Natural's Num -- instance has similar problems to Natural's. data Ratio a (:%) :: !a -> !a -> 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 ratioPrec :: Int ratioPrec1 :: Int infinity :: Rational notANumber :: Rational -- | reduce is a subsidiary function used only in this module. It -- normalises a ratio by dividing both numerator and denominator by their -- greatest common divisor. reduce :: Integral a => a -> a -> Ratio a -- | 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 -- | Real numbers. -- -- The Haskell report defines no laws for Real, however -- Real instances are customarily expected to adhere to the -- following law: -- -- -- -- The law does not hold for Float, Double, CFloat, -- CDouble, etc., because these types contain non-finite values, -- which cannot be roundtripped through Rational. 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. -- -- The Haskell Report defines no laws for Integral. However, -- Integral instances are customarily expected to define a -- Euclidean domain and have the following properties for the -- div/mod and quot/rem pairs, given suitable -- Euclidean functions f and g: -- -- -- -- An example of a suitable Euclidean function, for Integer's -- instance, is abs. -- -- In addition, toInteger should be total, and -- fromInteger should be a left inverse for it, i.e. -- fromInteger (toInteger i) = i. class (Real a, Enum a) => Integral a -- | integer division truncated toward zero -- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. quot :: Integral a => a -> a -> a -- | integer remainder, satisfying -- --
--   (x `quot` y)*y + (x `rem` y) == x
--   
-- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. rem :: Integral a => a -> a -> a -- | integer division truncated toward negative infinity -- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. div :: Integral a => a -> a -> a -- | integer modulus, satisfying -- --
--   (x `div` y)*y + (x `mod` y) == x
--   
-- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. mod :: Integral a => a -> a -> a -- | simultaneous quot and rem -- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. quotRem :: Integral a => a -> a -> (a, a) -- | simultaneous div and mod -- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. divMod :: Integral a => a -> a -> (a, a) -- | conversion to Integer toInteger :: Integral a => a -> Integer infixl 7 `quot` infixl 7 `rem` infixl 7 `div` infixl 7 `mod` -- | Fractional numbers, supporting real division. -- -- The Haskell Report defines no laws for Fractional. However, -- (+) and (*) are customarily expected -- to define a division ring and have the following properties: -- -- -- -- Note that it isn't customarily expected that a type instance of -- Fractional implement a field. However, all instances in -- base do. 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 infixl 7 / -- | 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 numericEnumFrom :: Fractional a => a -> [a] numericEnumFromThen :: Fractional a => a -> a -> [a] numericEnumFromTo :: (Ord a, Fractional a) => a -> a -> [a] numericEnumFromThenTo :: (Ord a, Fractional a) => a -> a -> a -> [a] -- | General coercion from Integral types. -- -- WARNING: This function performs silent truncation if the result type -- is not at least as big as the argument's type. fromIntegral :: (Integral a, Num b) => a -> b -- | General coercion to Fractional types. -- -- WARNING: This function goes through the Rational type, which -- does not have values for NaN for example. This means it does -- not round-trip. -- -- For Double it also behaves differently with or without -O0: -- --
--   Prelude> realToFrac nan -- With -O0
--   -Infinity
--   Prelude> realToFrac nan
--   NaN
--   
realToFrac :: (Real a, Fractional b) => a -> b -- | Converts a possibly-negative Real value to a string. showSigned :: Real a => (a -> ShowS) -> Int -> a -> ShowS even :: Integral a => a -> Bool odd :: Integral a => a -> Bool -- | raise a number to a non-negative integral power (^) :: (Num a, Integral b) => a -> b -> a infixr 8 ^ powImpl :: (Num a, Integral b) => a -> b -> a powImplAcc :: (Num a, Integral b) => a -> b -> a -> a -- | raise a number to an integral power (^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 ^^ (^%^) :: Integral a => Rational -> a -> Rational (^^%^^) :: Integral a => Rational -> a -> Rational -- | 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 integralEnumFrom :: (Integral a, Bounded a) => a -> [a] integralEnumFromThen :: (Integral a, Bounded a) => a -> a -> [a] integralEnumFromTo :: Integral a => a -> a -> [a] integralEnumFromThenTo :: Integral a => a -> a -> a -> [a] data FractionalExponentBase Base2 :: FractionalExponentBase Base10 :: FractionalExponentBase mkRationalBase2 :: Rational -> Integer -> Rational mkRationalBase10 :: Rational -> Integer -> Rational mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational instance GHC.Real.Integral a => GHC.Enum.Enum (GHC.Real.Ratio a) instance GHC.Classes.Eq a => GHC.Classes.Eq (GHC.Real.Ratio a) instance GHC.Real.Integral a => GHC.Real.Fractional (GHC.Real.Ratio a) instance GHC.Real.Integral GHC.Types.Int instance GHC.Real.Integral GHC.Num.Integer.Integer instance GHC.Real.Integral GHC.Num.Natural.Natural instance GHC.Real.Integral GHC.Types.Word instance GHC.Real.Integral a => GHC.Num.Num (GHC.Real.Ratio a) instance GHC.Real.Integral a => GHC.Classes.Ord (GHC.Real.Ratio a) instance GHC.Real.Integral a => GHC.Real.RealFrac (GHC.Real.Ratio a) instance GHC.Real.Real GHC.Types.Int instance GHC.Real.Real GHC.Num.Integer.Integer instance GHC.Real.Real GHC.Num.Natural.Natural instance GHC.Real.Integral a => GHC.Real.Real (GHC.Real.Ratio a) instance GHC.Real.Real GHC.Types.Word instance GHC.Show.Show GHC.Real.FractionalExponentBase instance GHC.Show.Show a => GHC.Show.Show (GHC.Real.Ratio a) -- | GHC's Ix typeclass implementation. module GHC.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 -- | Like index, but without checking that the value is in range. unsafeIndex :: 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 -- | like rangeSize, but without checking that the upper bound is in -- range. unsafeRangeSize :: Ix a => (a, a) -> Int indexError :: Show a => (a, a) -> a -> String -> b instance GHC.Ix.Ix GHC.Types.Bool instance GHC.Ix.Ix GHC.Types.Char instance GHC.Ix.Ix GHC.Types.Int instance GHC.Ix.Ix GHC.Num.Integer.Integer instance GHC.Ix.Ix GHC.Num.Natural.Natural instance GHC.Ix.Ix GHC.Types.Ordering instance GHC.Ix.Ix a => GHC.Ix.Ix (GHC.Tuple.Prim.Solo a) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6, GHC.Ix.Ix a7, GHC.Ix.Ix a8, GHC.Ix.Ix a9, GHC.Ix.Ix aA) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6, GHC.Ix.Ix a7, GHC.Ix.Ix a8, GHC.Ix.Ix a9, GHC.Ix.Ix aA, GHC.Ix.Ix aB) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6, GHC.Ix.Ix a7, GHC.Ix.Ix a8, GHC.Ix.Ix a9, GHC.Ix.Ix aA, GHC.Ix.Ix aB, GHC.Ix.Ix aC) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6, GHC.Ix.Ix a7, GHC.Ix.Ix a8, GHC.Ix.Ix a9, GHC.Ix.Ix aA, GHC.Ix.Ix aB, GHC.Ix.Ix aC, GHC.Ix.Ix aD) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6, GHC.Ix.Ix a7, GHC.Ix.Ix a8, GHC.Ix.Ix a9, GHC.Ix.Ix aA, GHC.Ix.Ix aB, GHC.Ix.Ix aC, GHC.Ix.Ix aD, GHC.Ix.Ix aE) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6, GHC.Ix.Ix a7, GHC.Ix.Ix a8, GHC.Ix.Ix a9, GHC.Ix.Ix aA, GHC.Ix.Ix aB, GHC.Ix.Ix aC, GHC.Ix.Ix aD, GHC.Ix.Ix aE, GHC.Ix.Ix aF) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF) instance (GHC.Ix.Ix a, GHC.Ix.Ix b) => GHC.Ix.Ix (a, b) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3) => GHC.Ix.Ix (a1, a2, a3) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4) => GHC.Ix.Ix (a1, a2, a3, a4) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5) => GHC.Ix.Ix (a1, a2, a3, a4, a5) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6, GHC.Ix.Ix a7) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6, a7) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6, GHC.Ix.Ix a7, GHC.Ix.Ix a8) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6, a7, a8) instance (GHC.Ix.Ix a1, GHC.Ix.Ix a2, GHC.Ix.Ix a3, GHC.Ix.Ix a4, GHC.Ix.Ix a5, GHC.Ix.Ix a6, GHC.Ix.Ix a7, GHC.Ix.Ix a8, GHC.Ix.Ix a9) => GHC.Ix.Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9) instance GHC.Ix.Ix () instance GHC.Ix.Ix GHC.Base.Void instance GHC.Ix.Ix GHC.Types.Word -- | GHC's array implementation. module GHC.Arr -- | 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 -- | Like index, but without checking that the value is in range. unsafeIndex :: 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 -- | like rangeSize, but without checking that the upper bound is in -- range. unsafeRangeSize :: Ix a => (a, a) -> Int -- | The type of immutable non-strict (boxed) arrays with indices in -- i and elements in e. data Array i e Array :: !i -> !i -> {-# UNPACK #-} !Int -> Array# e -> Array i e -- | Mutable, boxed, non-strict arrays in the ST monad. The type -- arguments are as follows: -- -- data STArray s i e STArray :: !i -> !i -> {-# UNPACK #-} !Int -> MutableArray# s e -> STArray s i e arrEleBottom :: a -- | Construct an array with the specified bounds and containing values for -- given indices within these bounds. -- -- The array is undefined (i.e. bottom) if any index in the list is out -- of bounds. The Haskell 2010 Report further specifies that if any two -- associations in the list have the same index, the value at that index -- is undefined (i.e. bottom). However in GHC's implementation, the value -- at such an index is the value part of the last association with that -- index in the list. -- -- Because the indices must be checked for these errors, array is -- strict in the bounds argument and in the indices of the association -- list, but non-strict in the values. Thus, recurrences such as the -- following are possible: -- --
--   a = array (1,100) ((1,1) : [(i, i * a!(i-1)) | i <- [2..100]])
--   
-- -- Not every index within the bounds of the array need appear in the -- association list, but the values associated with indices that do not -- appear will be undefined (i.e. bottom). -- -- If, in any dimension, the lower bound is greater than the upper bound, -- then the array is legal, but empty. Indexing an empty array always -- gives an array-bounds error, but bounds still yields the bounds -- with which the array was constructed. array :: Ix i => (i, i) -> [(i, e)] -> Array i e -- | Construct an array from a pair of bounds and a list of values in index -- order. listArray :: Ix i => (i, i) -> [e] -> Array i e -- | The value at the given index in an array. (!) :: Ix i => Array i e -> i -> e infixl 9 ! safeRangeSize :: Ix i => (i, i) -> Int negRange :: Int safeIndex :: Ix i => (i, i) -> Int -> i -> Int -- | Used to throw exceptions in array bounds-checking functions. -- -- ⚠ This function throws SomeException in all cases. -- --

Examples

-- --
--   >>> badSafeIndex 2 5
--   *** Exception: Error in array index; 2 not in range [0..5)
--   
badSafeIndex :: Int -> Int -> Int -- | The bounds with which an array was constructed. bounds :: Array i e -> (i, i) -- | The number of elements in the array. numElements :: Array i e -> Int numElementsSTArray :: STArray s i e -> Int -- | The list of indices of an array in ascending order. indices :: Ix i => Array i e -> [i] -- | The list of elements of an array in index order. elems :: Array i e -> [e] -- | The list of associations of an array in index order. assocs :: Ix i => Array i e -> [(i, e)] -- | The accumArray function deals with repeated indices in the -- association list using an accumulating function which combines -- the values of associations with the same index. -- -- For example, given a list of values of some index type, hist -- produces a histogram of the number of occurrences of each index within -- a specified range: -- --
--   hist :: (Ix a, Num b) => (a,a) -> [a] -> Array a b
--   hist bnds is = accumArray (+) 0 bnds [(i, 1) | i<-is, inRange bnds i]
--   
-- -- accumArray is strict in each result of applying the -- accumulating function, although it is lazy in the initial value. Thus, -- unlike arrays built with array, accumulated arrays should not -- in general be recursive. accumArray :: Ix i => (e -> a -> e) -> e -> (i, i) -> [(i, a)] -> Array i e adjust :: (e -> a -> e) -> MutableArray# s e -> (Int, a) -> STRep s b -> STRep s b -- | Constructs an array identical to the first argument except that it has -- been updated by the associations in the right argument. For example, -- if m is a 1-origin, n by n matrix, then -- --
--   m//[((i,i), 0) | i <- [1..n]]
--   
-- -- is the same matrix, except with the diagonal zeroed. -- -- Repeated indices in the association list are handled as for -- array: Haskell 2010 specifies that the resulting array is -- undefined (i.e. bottom), but GHC's implementation uses the last -- association for each index. (//) :: Ix i => Array i e -> [(i, e)] -> Array i e infixl 9 // -- | accum f takes an array and an association list and -- accumulates pairs from the list into the array with the accumulating -- function f. Thus accumArray can be defined using -- accum: -- --
--   accumArray f z b = accum f (array b [(i, z) | i <- range b])
--   
-- -- accum is strict in all the results of applying the -- accumulation. However, it is lazy in the initial values of the array. accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e amap :: (a -> b) -> Array i a -> Array i b -- | ixmap allows for transformations on array indices. It may be -- thought of as providing function composition on the right with the -- mapping that the original array embodies. -- -- A similar transformation of array values may be achieved using -- fmap from the Array instance of the Functor -- class. ixmap :: (Ix i, Ix j) => (i, i) -> (i -> j) -> Array j e -> Array i e eqArray :: (Ix i, Eq e) => Array i e -> Array i e -> Bool cmpArray :: (Ix i, Ord e) => Array i e -> Array i e -> Ordering cmpIntArray :: Ord e => Array Int e -> Array Int e -> Ordering newSTArray :: Ix i => (i, i) -> e -> ST s (STArray s i e) boundsSTArray :: STArray s i e -> (i, i) readSTArray :: Ix i => STArray s i e -> i -> ST s e writeSTArray :: Ix i => STArray s i e -> i -> e -> ST s () freezeSTArray :: STArray s i e -> ST s (Array i e) thawSTArray :: Array i e -> ST s (STArray s i e) -- | A left fold over the elements foldlElems :: (b -> a -> b) -> b -> Array i a -> b -- | A strict left fold over the elements foldlElems' :: (b -> a -> b) -> b -> Array i a -> b -- | A left fold over the elements with no starting value foldl1Elems :: (a -> a -> a) -> Array i a -> a -- | A right fold over the elements foldrElems :: (a -> b -> b) -> b -> Array i a -> b -- | A strict right fold over the elements foldrElems' :: (a -> b -> b) -> b -> Array i a -> b -- | A right fold over the elements with no starting value foldr1Elems :: (a -> a -> a) -> Array i a -> a fill :: MutableArray# s e -> (Int, e) -> STRep s a -> STRep s a done :: i -> i -> Int -> MutableArray# s e -> STRep s (Array i e) unsafeArray :: Ix i => (i, i) -> [(Int, e)] -> Array i e unsafeArray' :: (i, i) -> Int -> [(Int, e)] -> Array i e lessSafeIndex :: Ix i => (i, i) -> Int -> i -> Int unsafeAt :: Array i e -> Int -> e unsafeReplace :: Array i e -> [(Int, e)] -> Array i e unsafeAccumArray :: Ix i => (e -> a -> e) -> e -> (i, i) -> [(Int, a)] -> Array i e unsafeAccumArray' :: (e -> a -> e) -> e -> (i, i) -> Int -> [(Int, a)] -> Array i e unsafeAccum :: (e -> a -> e) -> Array i e -> [(Int, a)] -> Array i e unsafeReadSTArray :: STArray s i e -> Int -> ST s e unsafeWriteSTArray :: STArray s i e -> Int -> e -> ST s () unsafeFreezeSTArray :: STArray s i e -> ST s (Array i e) unsafeThawSTArray :: Array i e -> ST s (STArray s i e) instance (GHC.Ix.Ix i, GHC.Classes.Eq e) => GHC.Classes.Eq (GHC.Arr.Array i e) instance GHC.Classes.Eq (GHC.Arr.STArray s i e) instance GHC.Base.Functor (GHC.Arr.Array i) instance (GHC.Ix.Ix i, GHC.Classes.Ord e) => GHC.Classes.Ord (GHC.Arr.Array i e) instance (GHC.Ix.Ix a, GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (GHC.Arr.Array a b) -- | 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 GHC.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 -- | x `testBit` i is the same as x .&. bit n /= 0 -- -- In other words it returns True if the bit at offset @n is set. -- -- 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. -- -- Default implementation based upon bitSizeMaybe provided since -- 4.12.0.0. -- | 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). Some instances may throw an Overflow exception -- if given a negative input. -- -- 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. Some instances may throw an -- Overflow exception if given a negative input. -- -- 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 and 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 infixl 7 .&. infixl 5 .|. infixl 6 `xor` infixl 8 `shift` infixl 8 `rotate` infixl 8 `shiftL` infixl 8 `shiftR` infixl 8 `rotateL` infixl 8 `rotateR` -- | 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 == toInteger y = Just y
--     | otherwise                  = Nothing
--     where
--       y = fromIntegral 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 GHC.Bits.Bits GHC.Types.Bool instance GHC.Bits.Bits GHC.Types.Int instance GHC.Bits.Bits GHC.Num.Integer.Integer instance GHC.Bits.Bits GHC.Num.Natural.Natural instance GHC.Bits.Bits GHC.Types.Word instance GHC.Bits.FiniteBits GHC.Types.Bool instance GHC.Bits.FiniteBits GHC.Types.Int instance GHC.Bits.FiniteBits GHC.Types.Word -- | This module exports: -- -- module GHC.TypeError -- | 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 infixl 6 :<>: infixl 5 :$$: -- | 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.")
--   
type family TypeError (a :: ErrorMessage) :: b -- | A type-level assert function. -- -- If the first argument evaluates to true, then the empty constraint is -- returned, otherwise the second argument (which is intended to be -- something which reduces to TypeError is used). -- -- For example, given some type level predicate P' :: Type -> -- Bool, it is possible to write the type synonym -- --
--   type P a = Assert (P' a) (NotPError a)
--   
-- -- where NotPError reduces to a TypeError which is -- reported if the assertion fails. type family Assert (check :: Bool) errMsg -- | An unsatisfiable constraint. Similar to TypeError when used at -- the Constraint kind, but reports errors in a more predictable -- manner. -- -- See also the unsatisfiable function. -- -- since 4.19.0.0. class Unsatisfiable (msg :: ErrorMessage) -- | Prove anything within a context with an Unsatisfiable -- constraint. -- -- This is useful for filling in instance methods when there is an -- Unsatisfiable constraint in the instance head, e.g.: -- --
--   instance Unsatisfiable (Text "No Eq instance for functions") => Eq (a -> b) where
--   
-- -- (==) = unsatisfiable -- -- since 4.19.0.0. unsatisfiable :: forall (msg :: ErrorMessage) a. Unsatisfiable msg => a -- | DO NOT USE THIS MODULE. Use GHC.TypeLits instead. -- -- This module is internal-only and was exposed by accident. It may be -- removed without warning in a future version. -- -- (The technical reason for this module's existence is that it is needed -- to prevent module cycles while still allowing these identifiers to be -- imported in Ord.) module GHC.TypeLits.Internal -- | (Kind) This is the kind of type-level symbols. data Symbol -- | Comparison of type-level symbols, as a function. type family CmpSymbol (a :: Symbol) (b :: Symbol) :: Ordering -- | Comparison of type-level characters. type family CmpChar (a :: Char) (b :: Char) :: Ordering -- | DO NOT USE THIS MODULE. Use GHC.TypeNats instead. -- -- This module is internal-only and was exposed by accident. It may be -- removed without warning in a future version. -- -- (The technical reason for this module's existence is that it is needed -- to prevent module cycles while still allowing these identifiers to be -- imported in Ord.) module GHC.TypeNats.Internal -- | Natural number -- -- Invariant: numbers <= 0xffffffffffffffff use the NS -- constructor data Natural -- | Comparison of type-level naturals, as a function. type family CmpNat (a :: Natural) (b :: Natural) :: Ordering -- | Implementations for the character predicates (isLower, isUpper, etc.) -- and the conversions (toUpper, toLower). The implementation uses -- libunicode on Unix systems if that is available. module GHC.Unicode -- | Version of Unicode standard used by base: 15.1.0. unicodeVersion :: Version -- | 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 -- | 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 control characters, which are the non-printing characters of -- the Latin-1 subset of Unicode. isControl :: 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 -- | Selects printable Unicode characters (letters, numbers, marks, -- punctuation, symbols and spaces). isPrint :: Char -> Bool -- | Returns True for any Unicode space character, and the control -- characters \t, \n, \r, \f, -- \v. isSpace :: 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. -- -- Note: this predicate does not work for letter-like -- characters such as: 'Ⓐ' (U+24B6 circled Latin -- capital letter A) and 'Ⅳ' (U+2163 Roman numeral -- four). This is due to selecting only characters with the -- GeneralCategory UppercaseLetter or -- TitlecaseLetter. -- -- See isUpperCase for a more intuitive predicate. Note that -- unlike isUpperCase, isUpper does select -- title-case characters such as 'Dž' (U+01C5 -- Latin capital letter d with small letter z with caron) or 'ᾯ' -- (U+1FAF Greek capital letter omega with dasia and perispomeni -- and prosgegrammeni). isUpper :: Char -> Bool -- | Selects upper-case Unicode letter-like characters. -- -- Note: this predicate selects characters with the Unicode -- property Uppercase, which include letter-like characters such -- as: 'Ⓐ' (U+24B6 circled Latin capital letter A) and -- 'Ⅳ' (U+2163 Roman numeral four). -- -- See isUpper for the legacy predicate. Note that unlike -- isUpperCase, isUpper does select title-case -- characters such as 'Dž' (U+01C5 Latin capital letter -- d with small letter z with caron) or 'ᾯ' (U+1FAF -- Greek capital letter omega with dasia and perispomeni and -- prosgegrammeni). isUpperCase :: Char -> Bool -- | Selects lower-case alphabetic Unicode characters (letters). -- -- Note: this predicate does not work for letter-like -- characters such as: 'ⓐ' (U+24D0 circled Latin small -- letter a) and 'ⅳ' (U+2173 small Roman numeral four). -- This is due to selecting only characters with the -- GeneralCategory LowercaseLetter. -- -- See isLowerCase for a more intuitive predicate. isLower :: Char -> Bool -- | Selects lower-case Unicode letter-like characters. -- -- Note: this predicate selects characters with the Unicode -- property Lowercase, which includes letter-like characters -- such as: 'ⓐ' (U+24D0 circled Latin small letter a) -- and 'ⅳ' (U+2173 small Roman numeral four). -- -- See isLower for the legacy predicate. isLowerCase :: 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 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 or numeric Unicode characters. -- -- Note that numeric digits outside the ASCII range, as well as numeric -- characters which aren't digits, are selected by this function but not -- by isDigit. Such characters may be part of identifiers but are -- not used by the printer and reader to represent numbers. isAlphaNum :: 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 -- | 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 instance GHC.Enum.Bounded GHC.Unicode.GeneralCategory instance GHC.Enum.Enum GHC.Unicode.GeneralCategory instance GHC.Classes.Eq GHC.Unicode.GeneralCategory instance GHC.Ix.Ix GHC.Unicode.GeneralCategory instance GHC.Classes.Ord GHC.Unicode.GeneralCategory instance GHC.Show.Show GHC.Unicode.GeneralCategory -- | Sized unsigned integral types: Word, Word8, -- Word16, Word32, and Word64. module GHC.Word -- | A Word is an unsigned integral type, with the same size as -- Int. data Word W# :: Word# -> Word -- | 8-bit unsigned integer type data Word8 W8# :: Word8# -> Word8 -- | 16-bit unsigned integer type data Word16 W16# :: Word16# -> Word16 -- | 32-bit unsigned integer type data Word32 W32# :: Word32# -> Word32 -- | 64-bit unsigned integer type data Word64 W64# :: Word64# -> Word64 uncheckedShiftL64# :: Word64# -> Int# -> Word64# uncheckedShiftRL64# :: Word64# -> Int# -> Word64# -- | Reverse order of bytes in Word16. byteSwap16 :: Word16 -> Word16 -- | Reverse order of bytes in Word32. byteSwap32 :: Word32 -> Word32 -- | Reverse order of bytes in Word64. byteSwap64 :: Word64 -> Word64 -- | Reverse the order of the bits in a Word8. bitReverse8 :: Word8 -> Word8 -- | Reverse the order of the bits in a Word16. bitReverse16 :: Word16 -> Word16 -- | Reverse the order of the bits in a Word32. bitReverse32 :: Word32 -> Word32 -- | Reverse the order of the bits in a Word64. bitReverse64 :: Word64 -> Word64 eqWord :: Word -> Word -> Bool neWord :: Word -> Word -> Bool gtWord :: Word -> Word -> Bool geWord :: Word -> Word -> Bool ltWord :: Word -> Word -> Bool leWord :: Word -> Word -> Bool eqWord8 :: Word8 -> Word8 -> Bool neWord8 :: Word8 -> Word8 -> Bool gtWord8 :: Word8 -> Word8 -> Bool geWord8 :: Word8 -> Word8 -> Bool ltWord8 :: Word8 -> Word8 -> Bool leWord8 :: Word8 -> Word8 -> Bool eqWord16 :: Word16 -> Word16 -> Bool neWord16 :: Word16 -> Word16 -> Bool gtWord16 :: Word16 -> Word16 -> Bool geWord16 :: Word16 -> Word16 -> Bool ltWord16 :: Word16 -> Word16 -> Bool leWord16 :: Word16 -> Word16 -> Bool eqWord32 :: Word32 -> Word32 -> Bool neWord32 :: Word32 -> Word32 -> Bool gtWord32 :: Word32 -> Word32 -> Bool geWord32 :: Word32 -> Word32 -> Bool ltWord32 :: Word32 -> Word32 -> Bool leWord32 :: Word32 -> Word32 -> Bool eqWord64 :: Word64 -> Word64 -> Bool neWord64 :: Word64 -> Word64 -> Bool gtWord64 :: Word64 -> Word64 -> Bool geWord64 :: Word64 -> Word64 -> Bool ltWord64 :: Word64 -> Word64 -> Bool leWord64 :: Word64 -> Word64 -> Bool instance GHC.Bits.Bits GHC.Word.Word16 instance GHC.Bits.Bits GHC.Word.Word32 instance GHC.Bits.Bits GHC.Word.Word64 instance GHC.Bits.Bits GHC.Word.Word8 instance GHC.Enum.Bounded GHC.Word.Word16 instance GHC.Enum.Bounded GHC.Word.Word32 instance GHC.Enum.Bounded GHC.Word.Word64 instance GHC.Enum.Bounded GHC.Word.Word8 instance GHC.Enum.Enum GHC.Word.Word16 instance GHC.Enum.Enum GHC.Word.Word32 instance GHC.Enum.Enum GHC.Word.Word64 instance GHC.Enum.Enum GHC.Word.Word8 instance GHC.Classes.Eq GHC.Word.Word16 instance GHC.Classes.Eq GHC.Word.Word32 instance GHC.Classes.Eq GHC.Word.Word64 instance GHC.Classes.Eq GHC.Word.Word8 instance GHC.Bits.FiniteBits GHC.Word.Word16 instance GHC.Bits.FiniteBits GHC.Word.Word32 instance GHC.Bits.FiniteBits GHC.Word.Word64 instance GHC.Bits.FiniteBits GHC.Word.Word8 instance GHC.Real.Integral GHC.Word.Word16 instance GHC.Real.Integral GHC.Word.Word32 instance GHC.Real.Integral GHC.Word.Word64 instance GHC.Real.Integral GHC.Word.Word8 instance GHC.Ix.Ix GHC.Word.Word16 instance GHC.Ix.Ix GHC.Word.Word32 instance GHC.Ix.Ix GHC.Word.Word64 instance GHC.Ix.Ix GHC.Word.Word8 instance GHC.Num.Num GHC.Word.Word16 instance GHC.Num.Num GHC.Word.Word32 instance GHC.Num.Num GHC.Word.Word64 instance GHC.Num.Num GHC.Word.Word8 instance GHC.Classes.Ord GHC.Word.Word16 instance GHC.Classes.Ord GHC.Word.Word32 instance GHC.Classes.Ord GHC.Word.Word64 instance GHC.Classes.Ord GHC.Word.Word8 instance GHC.Real.Real GHC.Word.Word16 instance GHC.Real.Real GHC.Word.Word32 instance GHC.Real.Real GHC.Word.Word64 instance GHC.Real.Real GHC.Word.Word8 instance GHC.Show.Show GHC.Word.Word16 instance GHC.Show.Show GHC.Word.Word32 instance GHC.Show.Show GHC.Word.Word64 instance GHC.Show.Show GHC.Word.Word8 -- | The types Float and Double, the classes Floating -- and RealFloat and casting between Word32 and Float and Word64 -- and Double. module GHC.Float -- | Trigonometric and hyperbolic functions and related functions. -- -- The Haskell Report defines no laws for Floating. However, -- (+), (*) and exp are -- customarily expected to define an exponential field and have the -- following properties: -- -- class Fractional a => Floating a pi :: Floating a => a exp :: Floating a => a -> a log :: Floating a => a -> a sqrt :: Floating a => a -> a (**) :: Floating a => a -> a -> a logBase :: Floating a => a -> a -> a sin :: Floating a => a -> a cos :: Floating a => a -> a tan :: Floating a => a -> a asin :: Floating a => a -> a acos :: Floating a => a -> a atan :: Floating a => a -> a sinh :: Floating a => a -> a cosh :: Floating a => a -> a tanh :: Floating a => a -> a asinh :: Floating a => a -> a acosh :: Floating a => a -> a 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 infixr 8 ** -- | 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 -- | Used to prevent exponent over/underflow when encoding floating point -- numbers. This is also the same as -- --
--   \(x,y) -> max (-x) (min x y)
--   
-- --

Example

-- --
--   >>> clamp (-10) 5
--   10
--   
clamp :: Int -> Int -> Int -- | 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) -- | Converts a Rational value into any type in class -- RealFloat. fromRat :: RealFloat a => Rational -> a formatRealFloat :: RealFloat a => FFFormat -> Maybe Int -> a -> String -- | Default implementation for log1mexp requiring -- Ord to test against a threshold to decide which -- implementation variant to use. log1mexpOrd :: (Ord a, Floating a) => a -> a plusFloat :: Float -> Float -> Float minusFloat :: Float -> Float -> Float negateFloat :: Float -> Float timesFloat :: Float -> Float -> Float fabsFloat :: Float -> Float -- | Convert an Integer to a Float# integerToFloat# :: Integer -> Float# -- | Converts a positive integer to a floating-point value. -- -- The value nearest to the argument will be returned. If there are two -- such values, the one with an even significand will be returned (i.e. -- IEEE roundTiesToEven). -- -- The argument must be strictly positive, and floatRadix (undefined -- :: a) must be 2. integerToBinaryFloat' :: RealFloat a => Integer -> a -- | Convert a Natural to a Float# naturalToFloat# :: Natural -> Float# divideFloat :: Float -> Float -> Float rationalToFloat :: Integer -> Integer -> Float fromRat'' :: RealFloat a => Int -> Int -> Integer -> Integer -> a properFractionFloat :: Integral b => Float -> (b, Float) truncateFloat :: Integral b => Float -> b roundFloat :: Integral b => Float -> b floorFloat :: Integral b => Float -> b ceilingFloat :: Integral b => Float -> b expFloat :: Float -> Float logFloat :: Float -> Float sqrtFloat :: Float -> Float sinFloat :: Float -> Float cosFloat :: Float -> Float tanFloat :: Float -> Float asinFloat :: Float -> Float acosFloat :: Float -> Float atanFloat :: Float -> Float sinhFloat :: Float -> Float coshFloat :: Float -> Float tanhFloat :: Float -> Float powerFloat :: Float -> Float -> Float asinhFloat :: Float -> Float acoshFloat :: Float -> Float atanhFloat :: Float -> Float log1pFloat :: Float -> Float expm1Float :: Float -> Float isFloatFinite :: Float -> Int isFloatNaN :: Float -> Int isFloatInfinite :: Float -> Int isFloatDenormalized :: Float -> Int isFloatNegativeZero :: Float -> Int showSignedFloat :: RealFloat a => (a -> ShowS) -> Int -> a -> ShowS plusDouble :: Double -> Double -> Double minusDouble :: Double -> Double -> Double negateDouble :: Double -> Double timesDouble :: Double -> Double -> Double fabsDouble :: Double -> Double -- | Convert an Integer to a Double# integerToDouble# :: Integer -> Double# -- | Encode a Natural (mantissa) into a Double# naturalToDouble# :: Natural -> Double# divideDouble :: Double -> Double -> Double rationalToDouble :: Integer -> Integer -> Double expDouble :: Double -> Double logDouble :: Double -> Double sqrtDouble :: Double -> Double sinDouble :: Double -> Double cosDouble :: Double -> Double tanDouble :: Double -> Double asinDouble :: Double -> Double acosDouble :: Double -> Double atanDouble :: Double -> Double sinhDouble :: Double -> Double coshDouble :: Double -> Double tanhDouble :: Double -> Double powerDouble :: Double -> Double -> Double asinhDouble :: Double -> Double acoshDouble :: Double -> Double atanhDouble :: Double -> Double log1pDouble :: Double -> Double expm1Double :: Double -> Double properFractionDouble :: Integral b => Double -> (b, Double) truncateDouble :: Integral b => Double -> b roundDouble :: Integral b => Double -> b ceilingDouble :: Integral b => Double -> b floorDouble :: Integral b => Double -> b isDoubleFinite :: Double -> Int isDoubleNaN :: Double -> Int isDoubleInfinite :: Double -> Int isDoubleDenormalized :: Double -> Int isDoubleNegativeZero :: Double -> Int data FFFormat FFExponent :: FFFormat FFFixed :: FFFormat FFGeneric :: FFFormat formatRealFloatAlt :: RealFloat a => FFFormat -> Maybe Int -> Bool -> a -> String roundTo :: Int -> Int -> [Int] -> (Int, [Int]) expt :: Integer -> Int -> Integer roundingMode# :: Integer -> Int# -> Int# fromRat' :: RealFloat a => Rational -> a minExpt :: Int maxExpt :: Int expts :: Array Int Integer maxExpt10 :: Int expts10 :: Array Int Integer gtFloat :: Float -> Float -> Bool geFloat :: Float -> Float -> Bool ltFloat :: Float -> Float -> Bool leFloat :: Float -> Float -> Bool gtDouble :: Double -> Double -> Bool geDouble :: Double -> Double -> Bool leDouble :: Double -> Double -> Bool ltDouble :: Double -> Double -> Bool double2Float :: Double -> Float float2Double :: Float -> Double word2Double :: Word -> Double word2Float :: Word -> Float -- | castWord32ToFloat w does a bit-for-bit copy from an -- integral value to a floating-point value. castWord32ToFloat :: Word32 -> Float stgWord32ToFloat :: Word32# -> Float# -- | castFloatToWord32 f does a bit-for-bit copy from a -- floating-point value to an integral value. castFloatToWord32 :: Float -> Word32 stgFloatToWord32 :: Float# -> Word32# -- | castWord64ToDouble w does a bit-for-bit copy from an -- integral value to a floating-point value. castWord64ToDouble :: Word64 -> Double stgWord64ToDouble :: Word64# -> Double# -- | castFloatToWord64 f does a bit-for-bit copy from a -- floating-point value to an integral value. castDoubleToWord64 :: Double -> Word64 stgDoubleToWord64 :: Double# -> Word64# -- | 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 data Float# :: TYPE 'FloatRep data Double# :: TYPE 'DoubleRep double2Int :: Double -> Int int2Double :: Int -> Double float2Int :: Float -> Int int2Float :: Int -> Float eqFloat :: Float -> Float -> Bool eqDouble :: Double -> Double -> Bool instance GHC.Enum.Enum GHC.Types.Double instance GHC.Enum.Enum GHC.Types.Float instance GHC.Float.Floating GHC.Types.Double instance GHC.Float.Floating GHC.Types.Float instance GHC.Real.Fractional GHC.Types.Double instance GHC.Real.Fractional GHC.Types.Float instance GHC.Num.Num GHC.Types.Double instance GHC.Num.Num GHC.Types.Float instance GHC.Real.Real GHC.Types.Double instance GHC.Real.Real GHC.Types.Float instance GHC.Float.RealFloat GHC.Types.Double instance GHC.Float.RealFloat GHC.Types.Float instance GHC.Real.RealFrac GHC.Types.Double instance GHC.Real.RealFrac GHC.Types.Float instance GHC.Show.Show GHC.Types.Double instance GHC.Show.Show GHC.Types.Float -- | The arbitrary-precision Natural number type. module Numeric.Natural -- | Natural number -- -- Invariant: numbers <= 0xffffffffffffffff use the NS -- constructor data Natural -- | Natural subtraction. Returns Nothings for non-positive -- results. minusNaturalMaybe :: Natural -> Natural -> Maybe Natural -- | 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 succeeds, 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.Alternative Text.ParserCombinators.ReadP.P instance GHC.Base.Alternative Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Applicative Text.ParserCombinators.ReadP.P instance GHC.Base.Applicative Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Functor Text.ParserCombinators.ReadP.P instance GHC.Base.Functor Text.ParserCombinators.ReadP.ReadP instance Control.Monad.Fail.MonadFail Text.ParserCombinators.ReadP.P instance Control.Monad.Fail.MonadFail Text.ParserCombinators.ReadP.ReadP instance GHC.Base.MonadPlus Text.ParserCombinators.ReadP.P instance GHC.Base.MonadPlus Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Monad Text.ParserCombinators.ReadP.P instance GHC.Base.Monad Text.ParserCombinators.ReadP.ReadP -- | 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.Alternative Text.ParserCombinators.ReadPrec.ReadPrec instance GHC.Base.Applicative Text.ParserCombinators.ReadPrec.ReadPrec instance GHC.Base.Functor Text.ParserCombinators.ReadPrec.ReadPrec instance Control.Monad.Fail.MonadFail Text.ParserCombinators.ReadPrec.ReadPrec instance GHC.Base.MonadPlus Text.ParserCombinators.ReadPrec.ReadPrec instance GHC.Base.Monad 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 readBinP :: (Eq a, Num a) => ReadP a 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.Classes.Eq Text.Read.Lex.Lexeme instance GHC.Classes.Eq Text.Read.Lex.Number instance GHC.Show.Show Text.Read.Lex.Lexeme instance GHC.Show.Show Text.Read.Lex.Number -- | The Read class and instances for basic data types. module GHC.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 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)] -- | 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 -- | 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 -- | Reads a non-empty string of decimal digits. lexDigits :: ReadS String -- | Parse a single lexeme lexP :: ReadPrec Lexeme expectP :: Lexeme -> ReadPrec () -- | (paren p) parses "(P0)" where p parses "P0" in -- precedence context zero paren :: ReadPrec a -> ReadPrec a -- | (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 -- | (list p) parses a list of things parsed by p, using -- the usual square-bracket syntax. list :: ReadPrec a -> ReadPrec [a] -- | Parse the specified lexeme and continue as specified. Esp useful for -- nullary constructors; e.g. choose [("A", return A), ("B", return -- B)] We match both Ident and Symbol because the constructor might -- be an operator eg (:~:) choose :: [(String, 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] readNumber :: Num a => (Lexeme -> ReadPrec a) -> ReadPrec a -- | Read parser for a record field, of the form -- fieldName=value. The fieldName must be an -- alphanumeric identifier; for symbols (operator-style) field names, -- e.g. (#), use readSymField). The second argument is a -- parser for the field value. readField :: String -> ReadPrec a -> ReadPrec a -- | Read parser for a record field, of the form -- fieldName#=value. That is, an alphanumeric identifier -- fieldName followed by the symbol #. The second -- argument is a parser for the field value. -- -- Note that readField does not suffice for this purpose due to -- #5041. readFieldHash :: String -> ReadPrec a -> ReadPrec a -- | Read parser for a symbol record field, of the form -- (###)=value (where ### is the field name). The field -- name must be a symbol (operator-style), e.g. (#). For regular -- (alphanumeric) field names, use readField. The second argument -- is a parser for the field value. readSymField :: String -> ReadPrec a -> ReadPrec 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 instance (GHC.Ix.Ix a, GHC.Read.Read a, GHC.Read.Read b) => GHC.Read.Read (GHC.Arr.Array a b) instance GHC.Read.Read GHC.Types.Bool instance GHC.Read.Read GHC.Types.Char instance GHC.Read.Read GHC.Types.Double instance GHC.Read.Read GHC.Types.Float instance GHC.Read.Read GHC.Unicode.GeneralCategory instance GHC.Read.Read GHC.Types.Int instance GHC.Read.Read GHC.Num.Integer.Integer instance GHC.Read.Read Text.Read.Lex.Lexeme instance GHC.Read.Read a => GHC.Read.Read [a] instance GHC.Read.Read a => GHC.Read.Read (GHC.Maybe.Maybe a) instance GHC.Read.Read GHC.Num.Natural.Natural instance GHC.Read.Read a => GHC.Read.Read (GHC.Base.NonEmpty a) instance GHC.Read.Read GHC.Types.Ordering instance (GHC.Real.Integral a, GHC.Read.Read a) => GHC.Read.Read (GHC.Real.Ratio a) instance GHC.Read.Read a => GHC.Read.Read (GHC.Tuple.Prim.Solo a) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f, GHC.Read.Read g, GHC.Read.Read h, GHC.Read.Read i, GHC.Read.Read j) => GHC.Read.Read (a, b, c, d, e, f, g, h, i, j) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f, GHC.Read.Read g, GHC.Read.Read h, GHC.Read.Read i, GHC.Read.Read j, GHC.Read.Read k) => GHC.Read.Read (a, b, c, d, e, f, g, h, i, j, k) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f, GHC.Read.Read g, GHC.Read.Read h, GHC.Read.Read i, GHC.Read.Read j, GHC.Read.Read k, GHC.Read.Read l) => GHC.Read.Read (a, b, c, d, e, f, g, h, i, j, k, l) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f, GHC.Read.Read g, GHC.Read.Read h, GHC.Read.Read i, GHC.Read.Read j, GHC.Read.Read k, GHC.Read.Read l, GHC.Read.Read m) => GHC.Read.Read (a, b, c, d, e, f, g, h, i, j, k, l, m) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f, GHC.Read.Read g, GHC.Read.Read h, GHC.Read.Read i, GHC.Read.Read j, GHC.Read.Read k, GHC.Read.Read l, GHC.Read.Read m, GHC.Read.Read n) => GHC.Read.Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f, GHC.Read.Read g, GHC.Read.Read h, GHC.Read.Read i, GHC.Read.Read j, GHC.Read.Read k, GHC.Read.Read l, GHC.Read.Read m, GHC.Read.Read n, GHC.Read.Read o) => GHC.Read.Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) instance (GHC.Read.Read a, GHC.Read.Read b) => GHC.Read.Read (a, b) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c) => GHC.Read.Read (a, b, c) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d) => GHC.Read.Read (a, b, c, d) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e) => GHC.Read.Read (a, b, c, d, e) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f) => GHC.Read.Read (a, b, c, d, e, f) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f, GHC.Read.Read g) => GHC.Read.Read (a, b, c, d, e, f, g) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f, GHC.Read.Read g, GHC.Read.Read h) => GHC.Read.Read (a, b, c, d, e, f, g, h) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c, GHC.Read.Read d, GHC.Read.Read e, GHC.Read.Read f, GHC.Read.Read g, GHC.Read.Read h, GHC.Read.Read i) => GHC.Read.Read (a, b, c, d, e, f, g, h, i) instance GHC.Read.Read () instance GHC.Read.Read GHC.Base.Void instance GHC.Read.Read GHC.Types.Word instance GHC.Read.Read GHC.Word.Word16 instance GHC.Read.Read GHC.Word.Word32 instance GHC.Read.Read GHC.Word.Word64 instance GHC.Read.Read GHC.Word.Word8 -- | 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 => 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 2. showBin :: Integral a => a -> ShowS -- | Show non-negative Integral numbers in base 16. showHex :: Integral a => a -> ShowS -- | Show non-negative Integral numbers in base 8. showOct :: Integral 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 -- | Show a floating-point value in the hexadecimal format, similar to the -- %a specifier in C's printf. -- --
--   >>> showHFloat (212.21 :: Double) ""
--   "0x1.a86b851eb851fp7"
--   
--   >>> showHFloat (-12.76 :: Float) ""
--   "-0x1.9851ecp3"
--   
--   >>> showHFloat (-0 :: Double) ""
--   "-0x0p+0"
--   
showHFloat :: 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 binary notation. -- --
--   >>> readBin "10011"
--   [(19,"")]
--   
readBin :: (Eq a, Num a) => ReadS a -- | Read an unsigned number in decimal notation. -- --
--   >>> readDec "0644"
--   [(644,"")]
--   
readDec :: (Eq a, Num a) => ReadS a -- | Read an unsigned number in octal notation. -- --
--   >>> readOct "0644"
--   [(420,"")]
--   
readOct :: (Eq a, Num a) => ReadS a -- | Read an unsigned number in hexadecimal notation. Both upper or lower -- case letters are allowed. -- --
--   >>> readHex "deadbeef"
--   [(3735928559,"")]
--   
readHex :: (Eq a, Num a) => ReadS a -- | Reads an unsigned RealFrac value, expressed in decimal -- scientific notation. -- -- Note that this function takes time linear in the magnitude of its -- input which can scale exponentially with input size (e.g. -- "1e100000000" is a very large number while having a very -- small textual form). For this reason, users should take care to avoid -- using this function on untrusted input. Users needing to parse -- floating point values (e.g. Float) are encouraged to instead -- use read, which does not suffer from this issue. 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. -- -- The Haskell Report defines no laws for Floating. However, -- (+), (*) and exp are -- customarily expected to define an exponential field and have the -- following properties: -- -- class Fractional a => Floating a pi :: Floating a => a exp :: Floating a => a -> a log :: Floating a => a -> a sqrt :: Floating a => a -> a (**) :: Floating a => a -> a -> a logBase :: Floating a => a -> a -> a sin :: Floating a => a -> a cos :: Floating a => a -> a tan :: Floating a => a -> a asin :: Floating a => a -> a acos :: Floating a => a -> a atan :: Floating a => a -> a sinh :: Floating a => a -> a cosh :: Floating a => a -> a tanh :: Floating a => a -> a asinh :: Floating a => a -> a acosh :: Floating a => a -> a 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 infixr 8 ** -- | The Ptr and FunPtr types and operations. module GHC.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 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 -- | 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 -- | 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 instance GHC.Classes.Eq (GHC.Ptr.FunPtr a) instance GHC.Classes.Eq (GHC.Ptr.Ptr a) instance GHC.Classes.Ord (GHC.Ptr.FunPtr a) instance GHC.Classes.Ord (GHC.Ptr.Ptr a) instance GHC.Show.Show (GHC.Ptr.FunPtr a) instance GHC.Show.Show (GHC.Ptr.Ptr a) -- | ⚠ Warning: Starting base-4.18, this module is being -- deprecated. See -- https://gitlab.haskell.org/ghc/ghc/-/issues/21461 for more -- information. -- -- This module provides a small set of low-level functions for packing -- and unpacking a chunk of bytes. Used by code emitted by the compiler -- plus the prelude libraries. -- -- The programmer level view of packed strings is provided by a GHC -- system library PackedString. module GHC.Pack packCString# :: [Char] -> ByteArray# unpackCString :: Ptr a -> [Char] unpackCString# :: Addr# -> [Char] unpackNBytes# :: Addr# -> Int# -> [Char] unpackFoldrCString# :: Addr# -> (Char -> a -> a) -> a -> a unpackAppendCString# :: Addr# -> [Char] -> [Char] -- | This module provides typed const pointers to foreign data. It -- is part of the Foreign Function Interface (FFI). module Foreign.C.ConstPtr -- | A pointer with the C const qualifier. For instance, an -- argument of type ConstPtr CInt would be marshalled as -- const int*. -- -- While const-ness generally does not matter for ccall -- imports (since const and non-const pointers -- typically have equivalent calling conventions), it does matter for -- capi imports. See GHC #22043. newtype ConstPtr a ConstPtr :: Ptr a -> ConstPtr a [unConstPtr] :: ConstPtr a -> Ptr a instance GHC.Classes.Eq (Foreign.C.ConstPtr.ConstPtr a) instance GHC.Classes.Ord (Foreign.C.ConstPtr.ConstPtr a) instance GHC.Show.Show (Foreign.C.ConstPtr.ConstPtr a) module GHC.Fingerprint.Type data Fingerprint Fingerprint :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> Fingerprint instance GHC.Classes.Eq GHC.Fingerprint.Type.Fingerprint instance GHC.Classes.Ord GHC.Fingerprint.Type.Fingerprint instance GHC.Show.Show GHC.Fingerprint.Type.Fingerprint -- | The IOMode type module GHC.IO.IOMode -- | See openFile data IOMode ReadMode :: IOMode WriteMode :: IOMode AppendMode :: IOMode ReadWriteMode :: IOMode instance GHC.Enum.Enum GHC.IO.IOMode.IOMode instance GHC.Classes.Eq GHC.IO.IOMode.IOMode instance GHC.Ix.Ix GHC.IO.IOMode.IOMode instance GHC.Classes.Ord GHC.IO.IOMode.IOMode instance GHC.Read.Read GHC.IO.IOMode.IOMode instance GHC.Show.Show GHC.IO.IOMode.IOMode -- | 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 Word8 -- | 16-bit unsigned integer type data Word16 -- | 32-bit unsigned integer type data Word32 -- | 64-bit unsigned integer type data Word64 -- | Reverse order of bytes in Word16. byteSwap16 :: Word16 -> Word16 -- | Reverse order of bytes in Word32. byteSwap32 :: Word32 -> Word32 -- | Reverse order of bytes in Word64. byteSwap64 :: Word64 -> Word64 -- | Reverse the order of the bits in a Word8. bitReverse8 :: Word8 -> Word8 -- | Reverse the order of the bits in a Word16. bitReverse16 :: Word16 -> Word16 -- | Reverse the order of the bits in a Word32. bitReverse32 :: Word32 -> Word32 -- | Reverse the order of the bits in a Word64. bitReverse64 :: Word64 -> Word64 module GHC.Clock -- | Return monotonic time in seconds, since some unspecified starting -- point getMonotonicTime :: IO Double -- | Return monotonic time in nanoseconds, since some unspecified starting -- point getMonotonicTimeNSec :: IO Word64 -- | Definition of propositional equality (:~:). -- Pattern-matching on a variable of type (a :~: b) -- produces a proof that a ~ b. module Data.Type.Equality -- | Lifted, homogeneous equality. By lifted, we mean that it can be bogus -- (deferred type error). By homogeneous, the two types a and -- b must have the same kinds. class a ~# b => (a :: k) ~ (b :: k) infix 4 ~ -- | 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. -- -- In 0.7.0, the fixity was set to infix 4 to match the -- fixity of :~~:. class a ~# b => (a :: k0) ~~ (b :: k1) infix 4 ~~ -- | 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 :: k) :~: (b :: k) [Refl] :: forall {k} (a :: k). a :~: a infix 4 :~: -- | 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] :: forall {k1} (a :: k1). a :~~: a infix 4 :~~: -- | Symmetry of equality sym :: forall {k} (a :: k) (b :: k). (a :~: b) -> b :~: a -- | Transitivity of equality trans :: forall {k} (a :: k) (b :: k) (c :: k). (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 :: forall {k} (a :: k) (b :: k) r. (a :~: b) -> (a ~ b => r) -> r -- | Apply one equality to another, respectively apply :: forall {k1} {k2} (f :: k1 -> k2) (g :: k1 -> k2) (a :: k1) (b :: k1). (f :~: g) -> (a :~: b) -> f a :~: g b -- | Extract equality of the arguments from an equality of applied types inner :: forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (g :: k1 -> k2) (b :: k1). (f a :~: g b) -> a :~: b -- | Extract equality of type constructors from an equality of applied -- types outer :: forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (g :: k1 -> k2) (b :: k1). (f a :~: g b) -> f :~: g -- | This class contains types where you can learn the equality of two -- types from information contained in terms. -- -- The result should be Just Refl if and only if the types -- applied to f are equal: -- --
--   testEquality (x :: f a) (y :: f b) = Just Refl ⟺ a = b
--   
-- -- Typically, only singleton types should inhabit this class. In that -- case type argument equality coincides with term equality: -- --
--   testEquality (x :: f a) (y :: f b) = Just Refl ⟺ a = b ⟺ x = y
--   
-- --
--   isJust (testEquality x y) = x == y
--   
-- -- Singleton types are not required, however, and so the latter two -- would-be laws are not in fact valid in general. class TestEquality (f :: k -> Type) -- | Conditionally prove the equality of a and b. testEquality :: forall (a :: k) (b :: k). TestEquality f => f a -> f b -> Maybe (a :~: b) -- | A type family to compute Boolean equality. type family (a :: k) == (b :: k) :: Bool infix 4 == instance forall k (a :: k) (b :: k). (a GHC.Types.~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~: b) instance forall k1 k2 (a :: k1) (b :: k2). (a GHC.Types.~~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~~: b) instance forall k (a :: k) (b :: k). (a GHC.Types.~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~: b) instance forall k1 k2 (a :: k1) (b :: k2). (a GHC.Types.~~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~~: b) instance forall k (a :: k) (b :: k). GHC.Classes.Eq (a Data.Type.Equality.:~: b) instance forall k1 k2 (a :: k1) (b :: k2). GHC.Classes.Eq (a Data.Type.Equality.:~~: b) instance forall k (a :: k) (b :: k). GHC.Classes.Ord (a Data.Type.Equality.:~: b) instance forall k1 k2 (a :: k1) (b :: k2). GHC.Classes.Ord (a Data.Type.Equality.:~~: b) instance forall k (a :: k) (b :: k). (a GHC.Types.~ b) => GHC.Read.Read (a Data.Type.Equality.:~: b) instance forall k1 k2 (a :: k1) (b :: k2). (a GHC.Types.~~ b) => GHC.Read.Read (a Data.Type.Equality.:~~: b) instance forall k (a :: k) (b :: k). GHC.Show.Show (a Data.Type.Equality.:~: b) instance forall k1 k2 (a :: k1) (b :: k2). GHC.Show.Show (a Data.Type.Equality.:~~: b) instance forall k (a :: k). Data.Type.Equality.TestEquality ((Data.Type.Equality.:~:) a) instance forall k1 k (a :: k1). Data.Type.Equality.TestEquality ((Data.Type.Equality.:~~:) a) -- | 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 :: k) (b :: k) [Coercion] :: forall {k} (a :: k) (b :: k). 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 :: forall {k} (a :: k) (b :: k) r. Coercion a b -> (Coercible a b => r) -> r -- | Symmetry of representational equality sym :: forall {k} (a :: k) (b :: k). Coercion a b -> Coercion b a -- | Transitivity of representational equality trans :: forall {k} (a :: k) (b :: k) (c :: k). Coercion a b -> Coercion b c -> Coercion a c -- | Convert propositional (nominal) equality to representational equality repr :: forall {k} (a :: k) (b :: k). (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 :: k -> Type) -- | Conditionally prove the representational equality of a and -- b. testCoercion :: forall (a :: k) (b :: k). TestCoercion f => f a -> f b -> Maybe (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) (b :: k). GHC.Types.Coercible a b => GHC.Enum.Enum (Data.Type.Coercion.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.Classes.Ord (Data.Type.Coercion.Coercion a b) 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.Show.Show (Data.Type.Coercion.Coercion a b) instance forall k (a :: k). Data.Type.Coercion.TestCoercion ((Data.Type.Equality.:~:) a) instance forall k1 k (a :: k1). Data.Type.Coercion.TestCoercion ((Data.Type.Equality.:~~:) a) instance forall k (a :: k). Data.Type.Coercion.TestCoercion (Data.Type.Coercion.Coercion a) module Control.Category -- | A class for categories. Instances should satisfy the laws -- -- class Category (cat :: k -> k -> Type) -- | the identity morphism id :: forall (a :: k). Category cat => cat a a -- | morphism composition (.) :: forall (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c infixr 9 . -- | Right-to-left composition (<<<) :: forall {k} cat (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c infixr 1 <<< -- | Left-to-right composition (>>>) :: forall {k} cat (a :: k) (b :: k) (c :: k). 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 -- | Proxy is a type that holds no data, but has a phantom parameter -- of arbitrary type (or even kind). Its use is to provide type -- information, even though there is no value available of that type (or -- it may be too costly to create one). -- -- Historically, Proxy :: Proxy a is a safer -- alternative to the undefined :: a idiom. -- --
--   >>> Proxy :: Proxy (Void, Int -> Int)
--   Proxy
--   
-- -- Proxy can even hold types of higher kinds, -- --
--   >>> Proxy :: Proxy Either
--   Proxy
--   
-- --
--   >>> Proxy :: Proxy Functor
--   Proxy
--   
-- --
--   >>> Proxy :: Proxy complicatedStructure
--   Proxy
--   
data Proxy (t :: k) Proxy :: Proxy (t :: k) -- | 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. -- --
--   >>> import Data.Word
--   
--   >>> :type asProxyTypeOf 123 (Proxy :: Proxy Word8)
--   asProxyTypeOf 123 (Proxy :: Proxy Word8) :: Word8
--   
-- -- Note the lower-case proxy in the definition. This allows any -- type constructor with just one argument to be passed to the function, -- for example we could also write -- --
--   >>> import Data.Word
--   
--   >>> :type asProxyTypeOf 123 (Just (undefined :: Word8))
--   asProxyTypeOf 123 (Just (undefined :: Word8)) :: Word8
--   
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 t instance GHC.Base.Alternative Data.Proxy.Proxy instance GHC.Base.Applicative Data.Proxy.Proxy instance forall k (t :: k). GHC.Enum.Bounded (Data.Proxy.Proxy t) instance forall k (s :: k). GHC.Enum.Enum (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Classes.Eq (Data.Proxy.Proxy s) instance GHC.Base.Functor Data.Proxy.Proxy instance forall k (s :: k). GHC.Ix.Ix (Data.Proxy.Proxy s) instance GHC.Base.MonadPlus Data.Proxy.Proxy instance GHC.Base.Monad Data.Proxy.Proxy instance forall k (s :: k). GHC.Base.Monoid (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Classes.Ord (Data.Proxy.Proxy s) instance forall k (t :: k). GHC.Read.Read (Data.Proxy.Proxy t) instance forall k (s :: k). GHC.Base.Semigroup (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Show.Show (Data.Proxy.Proxy s) -- | 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.Base.Applicative (Data.Either.Either e) instance (GHC.Classes.Eq a, GHC.Classes.Eq b) => GHC.Classes.Eq (Data.Either.Either a b) instance GHC.Base.Functor (Data.Either.Either a) instance GHC.Base.Monad (Data.Either.Either e) instance (GHC.Classes.Ord a, GHC.Classes.Ord b) => GHC.Classes.Ord (Data.Either.Either a b) instance (GHC.Read.Read a, GHC.Read.Read b) => GHC.Read.Read (Data.Either.Either a b) instance GHC.Base.Semigroup (Data.Either.Either a b) instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Data.Either.Either a b) -- | 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 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 fails with an -- error if the parse is unsuccessful, and it is therefore -- discouraged from being used in real applications. Use readMaybe -- or readEither for safe alternatives. -- --
--   >>> read "123" :: Int
--   123
--   
-- --
--   >>> read "hello" :: Int
--   *** Exception: Prelude.read: no parse
--   
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 "123" :: Either String Int
--   Right 123
--   
-- --
--   >>> readEither "hello" :: Either String Int
--   Left "Prelude.read: no parse"
--   
readEither :: Read a => String -> Either String a -- | Parse a string using the Read instance. Succeeds if there is -- exactly one valid result. -- --
--   >>> readMaybe "123" :: Maybe Int
--   Just 123
--   
-- --
--   >>> readMaybe "hello" :: Maybe Int
--   Nothing
--   
readMaybe :: Read a => String -> Maybe a -- | The Char type and associated operations. module Data.Char -- | The character type Char represents Unicode codespace and its -- elements are code points as in definitions D9 and D10 of the -- Unicode Standard. -- -- Character literals in Haskell are single-quoted: 'Q', -- 'Я' or 'Ω'. To represent a single quote itself use -- '\'', and to represent a backslash use '\\'. The -- full grammar can be found in the section 2.6 of the Haskell 2010 -- Language Report. -- -- To specify a character by its code point one can use decimal, -- hexadecimal or octal notation: '\65', '\x41' and -- '\o101' are all alternative forms of 'A'. The -- largest code point is '\x10ffff'. -- -- There is a special escape syntax for ASCII control characters: -- -- TODO: table -- -- Data.Char provides utilities to work with Char. 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). -- -- Note: this predicate does not work for letter-like -- characters such as: 'ⓐ' (U+24D0 circled Latin small -- letter a) and 'ⅳ' (U+2173 small Roman numeral four). -- This is due to selecting only characters with the -- GeneralCategory LowercaseLetter. -- -- See isLowerCase for a more intuitive predicate. isLower :: Char -> Bool -- | Selects lower-case Unicode letter-like characters. -- -- Note: this predicate selects characters with the Unicode -- property Lowercase, which includes letter-like characters -- such as: 'ⓐ' (U+24D0 circled Latin small letter a) -- and 'ⅳ' (U+2173 small Roman numeral four). -- -- See isLower for the legacy predicate. isLowerCase :: 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. -- -- Note: this predicate does not work for letter-like -- characters such as: 'Ⓐ' (U+24B6 circled Latin -- capital letter A) and 'Ⅳ' (U+2163 Roman numeral -- four). This is due to selecting only characters with the -- GeneralCategory UppercaseLetter or -- TitlecaseLetter. -- -- See isUpperCase for a more intuitive predicate. Note that -- unlike isUpperCase, isUpper does select -- title-case characters such as 'Dž' (U+01C5 -- Latin capital letter d with small letter z with caron) or 'ᾯ' -- (U+1FAF Greek capital letter omega with dasia and perispomeni -- and prosgegrammeni). isUpper :: Char -> Bool -- | Selects upper-case Unicode letter-like characters. -- -- Note: this predicate selects characters with the Unicode -- property Uppercase, which include letter-like characters such -- as: 'Ⓐ' (U+24B6 circled Latin capital letter A) and -- 'Ⅳ' (U+2163 Roman numeral four). -- -- See isUpper for the legacy predicate. Note that unlike -- isUpperCase, isUpper does select title-case -- characters such as 'Dž' (U+01C5 Latin capital letter -- d with small letter z with caron) or 'ᾯ' (U+1FAF -- Greek capital letter omega with dasia and perispomeni and -- prosgegrammeni). isUpperCase :: 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 Unicode characters. -- -- Note that numeric digits outside the ASCII range, as well as numeric -- characters which aren't digits, are selected by this function but not -- by isDigit. Such characters 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 'λ'
--   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 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 -- | x `testBit` i is the same as x .&. bit n /= 0 -- -- In other words it returns True if the bit at offset @n is set. -- -- 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. -- -- Default implementation based upon bitSizeMaybe provided since -- 4.12.0.0. -- | 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). Some instances may throw an Overflow exception -- if given a negative input. -- -- 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. Some instances may throw an -- Overflow exception if given a negative input. -- -- 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 and 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 infixl 7 .&. infixl 5 .|. infixl 6 `xor` infixl 8 `shift` infixl 8 `rotate` infixl 8 `shiftL` infixl 8 `shiftR` infixl 8 `rotateL` infixl 8 `rotateR` -- | 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 == toInteger y = Just y
--     | otherwise                  = Nothing
--     where
--       y = fromIntegral 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 -- | A more concise version of complement zeroBits. -- --
--   >>> complement (zeroBits :: Word) == (oneBits :: Word)
--   True
--   
-- --
--   >>> complement (oneBits :: Word) == (zeroBits :: Word)
--   True
--   
-- --

Note

-- -- The constraint on oneBits is arguably too strong. However, as -- some types (such as Natural) have undefined -- complement, this is the only safe choice. oneBits :: FiniteBits a => a -- | Infix version of xor. (.^.) :: Bits a => a -> a -> a infixl 6 .^. -- | Infix version of shiftR. (.>>.) :: Bits a => a -> Int -> a infixl 8 .>>. -- | Infix version of shiftL. (.<<.) :: Bits a => a -> Int -> a infixl 8 .<<. -- | Infix version of unsafeShiftR. (!>>.) :: Bits a => a -> Int -> a infixl 8 !>>. -- | Infix version of unsafeShiftL. (!<<.) :: Bits a => a -> Int -> a infixl 8 !<<. -- | Monoid under bitwise AND. -- --
--   >>> getAnd (And 0xab <> And 0x12) :: Word8
--   2
--   
newtype And a And :: a -> And a [getAnd] :: And a -> a -- | Monoid under bitwise inclusive OR. -- --
--   >>> getIor (Ior 0xab <> Ior 0x12) :: Word8
--   187
--   
newtype Ior a Ior :: a -> Ior a [getIor] :: Ior a -> a -- | Monoid under bitwise XOR. -- --
--   >>> getXor (Xor 0xab <> Xor 0x12) :: Word8
--   185
--   
newtype Xor a Xor :: a -> Xor a [getXor] :: Xor a -> a -- | Monoid under bitwise 'equality'; defined as 1 if the -- corresponding bits match, and 0 otherwise. -- --
--   >>> getIff (Iff 0xab <> Iff 0x12) :: Word8
--   70
--   
newtype Iff a Iff :: a -> Iff a [getIff] :: Iff a -> a instance GHC.Bits.Bits a => GHC.Bits.Bits (Data.Bits.And a) instance GHC.Bits.Bits a => GHC.Bits.Bits (Data.Bits.Iff a) instance GHC.Bits.Bits a => GHC.Bits.Bits (Data.Bits.Ior a) instance GHC.Bits.Bits a => GHC.Bits.Bits (Data.Bits.Xor a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Bits.And a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Bits.Iff a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Bits.Ior a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Bits.Xor a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Bits.And a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Bits.Iff a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Bits.Ior a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Bits.Xor a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Bits.And a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Bits.Iff a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Bits.Ior a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Bits.Xor a) instance GHC.Bits.FiniteBits a => GHC.Bits.FiniteBits (Data.Bits.And a) instance GHC.Bits.FiniteBits a => GHC.Bits.FiniteBits (Data.Bits.Iff a) instance GHC.Bits.FiniteBits a => GHC.Bits.FiniteBits (Data.Bits.Ior a) instance GHC.Bits.FiniteBits a => GHC.Bits.FiniteBits (Data.Bits.Xor a) instance GHC.Bits.FiniteBits a => GHC.Base.Monoid (Data.Bits.And a) instance GHC.Bits.FiniteBits a => GHC.Base.Monoid (Data.Bits.Iff a) instance GHC.Bits.Bits a => GHC.Base.Monoid (Data.Bits.Ior a) instance GHC.Bits.Bits a => GHC.Base.Monoid (Data.Bits.Xor a) instance GHC.Read.Read a => GHC.Read.Read (Data.Bits.And a) instance GHC.Read.Read a => GHC.Read.Read (Data.Bits.Iff a) instance GHC.Read.Read a => GHC.Read.Read (Data.Bits.Ior a) instance GHC.Read.Read a => GHC.Read.Read (Data.Bits.Xor a) instance GHC.Bits.Bits a => GHC.Base.Semigroup (Data.Bits.And a) instance GHC.Bits.FiniteBits a => GHC.Base.Semigroup (Data.Bits.Iff a) instance GHC.Bits.Bits a => GHC.Base.Semigroup (Data.Bits.Ior a) instance GHC.Bits.Bits a => GHC.Base.Semigroup (Data.Bits.Xor a) instance GHC.Show.Show a => GHC.Show.Show (Data.Bits.And a) instance GHC.Show.Show a => GHC.Show.Show (Data.Bits.Iff a) instance GHC.Show.Show a => GHC.Show.Show (Data.Bits.Ior a) instance GHC.Show.Show a => GHC.Show.Show (Data.Bits.Xor a) -- | The sized integral datatypes, Int8, Int16, Int32, -- and Int64. module GHC.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 I# :: Int# -> Int -- | 8-bit signed integer type data Int8 I8# :: Int8# -> Int8 -- | 16-bit signed integer type data Int16 I16# :: Int16# -> Int16 -- | 32-bit signed integer type data Int32 I32# :: Int32# -> Int32 -- | 64-bit signed integer type data Int64 I64# :: Int64# -> Int64 uncheckedIShiftL64# :: Int64# -> Int# -> Int64# uncheckedIShiftRA64# :: Int64# -> Int# -> Int64# shiftRLInt8# :: Int8# -> Int# -> Int8# shiftRLInt16# :: Int16# -> Int# -> Int16# shiftRLInt32# :: Int32# -> Int# -> Int32# eqInt :: Int -> Int -> Bool neInt :: Int -> Int -> Bool gtInt :: Int -> Int -> Bool geInt :: Int -> Int -> Bool ltInt :: Int -> Int -> Bool leInt :: Int -> Int -> Bool eqInt8 :: Int8 -> Int8 -> Bool neInt8 :: Int8 -> Int8 -> Bool gtInt8 :: Int8 -> Int8 -> Bool geInt8 :: Int8 -> Int8 -> Bool ltInt8 :: Int8 -> Int8 -> Bool leInt8 :: Int8 -> Int8 -> Bool eqInt16 :: Int16 -> Int16 -> Bool neInt16 :: Int16 -> Int16 -> Bool gtInt16 :: Int16 -> Int16 -> Bool geInt16 :: Int16 -> Int16 -> Bool ltInt16 :: Int16 -> Int16 -> Bool leInt16 :: Int16 -> Int16 -> Bool eqInt32 :: Int32 -> Int32 -> Bool neInt32 :: Int32 -> Int32 -> Bool gtInt32 :: Int32 -> Int32 -> Bool geInt32 :: Int32 -> Int32 -> Bool ltInt32 :: Int32 -> Int32 -> Bool leInt32 :: Int32 -> Int32 -> Bool eqInt64 :: Int64 -> Int64 -> Bool neInt64 :: Int64 -> Int64 -> Bool gtInt64 :: Int64 -> Int64 -> Bool geInt64 :: Int64 -> Int64 -> Bool ltInt64 :: Int64 -> Int64 -> Bool leInt64 :: Int64 -> Int64 -> Bool instance GHC.Bits.Bits GHC.Int.Int16 instance GHC.Bits.Bits GHC.Int.Int32 instance GHC.Bits.Bits GHC.Int.Int64 instance GHC.Bits.Bits GHC.Int.Int8 instance GHC.Enum.Bounded GHC.Int.Int16 instance GHC.Enum.Bounded GHC.Int.Int32 instance GHC.Enum.Bounded GHC.Int.Int64 instance GHC.Enum.Bounded GHC.Int.Int8 instance GHC.Enum.Enum GHC.Int.Int16 instance GHC.Enum.Enum GHC.Int.Int32 instance GHC.Enum.Enum GHC.Int.Int64 instance GHC.Enum.Enum GHC.Int.Int8 instance GHC.Classes.Eq GHC.Int.Int16 instance GHC.Classes.Eq GHC.Int.Int32 instance GHC.Classes.Eq GHC.Int.Int64 instance GHC.Classes.Eq GHC.Int.Int8 instance GHC.Bits.FiniteBits GHC.Int.Int16 instance GHC.Bits.FiniteBits GHC.Int.Int32 instance GHC.Bits.FiniteBits GHC.Int.Int64 instance GHC.Bits.FiniteBits GHC.Int.Int8 instance GHC.Real.Integral GHC.Int.Int16 instance GHC.Real.Integral GHC.Int.Int32 instance GHC.Real.Integral GHC.Int.Int64 instance GHC.Real.Integral GHC.Int.Int8 instance GHC.Ix.Ix GHC.Int.Int16 instance GHC.Ix.Ix GHC.Int.Int32 instance GHC.Ix.Ix GHC.Int.Int64 instance GHC.Ix.Ix GHC.Int.Int8 instance GHC.Num.Num GHC.Int.Int16 instance GHC.Num.Num GHC.Int.Int32 instance GHC.Num.Num GHC.Int.Int64 instance GHC.Num.Num GHC.Int.Int8 instance GHC.Classes.Ord GHC.Int.Int16 instance GHC.Classes.Ord GHC.Int.Int32 instance GHC.Classes.Ord GHC.Int.Int64 instance GHC.Classes.Ord GHC.Int.Int8 instance GHC.Read.Read GHC.Int.Int16 instance GHC.Read.Read GHC.Int.Int32 instance GHC.Read.Read GHC.Int.Int64 instance GHC.Read.Read GHC.Int.Int8 instance GHC.Real.Real GHC.Int.Int16 instance GHC.Real.Real GHC.Int.Int32 instance GHC.Real.Real GHC.Int.Int64 instance GHC.Real.Real GHC.Int.Int8 instance GHC.Show.Show GHC.Int.Int16 instance GHC.Show.Show GHC.Int.Int32 instance GHC.Show.Show GHC.Int.Int64 instance GHC.Show.Show GHC.Int.Int8 -- | 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 Int8 -- | 16-bit signed integer type data Int16 -- | 32-bit signed integer type data Int32 -- | 64-bit signed integer type data Int64 -- | 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 module Unsafe.Coerce -- | unsafeCoerce coerces a value from one type to another, -- bypassing the type-checker. -- -- There are several legitimate ways to use unsafeCoerce: -- --
    --
  1. To coerce a lifted type such as Int to Any, put -- it in a list of Any, and then later coerce it back to -- Int before using it.
  2. --
  3. To produce e.g. (a+b) :~: (b+a) from unsafeCoerce -- Refl. Here the two sides really are the same type -- so nothing -- unsafe is happening -- but GHC is not clever enough to see it.
  4. --
  5. In Data.Typeable we have
  6. --
-- --
--   eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2).
--                TypeRep a -> TypeRep b -> Maybe (a :~~: b)
--   eqTypeRep a b
--     | sameTypeRep a b = Just (unsafeCoerce HRefl)
--     | otherwise       = Nothing
--   
--   
-- -- Here again, the unsafeCoerce HRefl is safe, because the two -- types really are the same -- but the proof of that relies on the -- complex, trusted implementation of Typeable. -- --
    --
  1. (superseded) The "reflection trick", which takes advantage of the -- fact that in class C a where { op :: ty }, we can safely -- coerce between C a and ty (which have different -- kinds!) because it's really just a newtype. Note: there is no -- guarantee, at all that this behavior will be supported into -- perpetuity. It is now preferred to use withDict in -- GHC.Magic.Dict, which is type-safe. See Note [withDict] in -- GHC.Tc.Instance.Class for details.
  2. --
  3. (superseded) Casting between two types which have exactly the same -- structure: between a newtype of T and T, or between types which differ -- only in "phantom" type parameters. It is now preferred to use -- coerce from Data.Coerce, which is type-safe.
  4. --
-- -- Other uses of unsafeCoerce are undefined. In particular, you -- should not use unsafeCoerce to cast a T to an algebraic data -- type D, unless T is also an algebraic data type. For example, do not -- cast Int->Int to Bool, even if you -- later cast that Bool back to Int->Int -- before applying it. The reasons have to do with GHC's internal -- representation details (for the cognoscenti, data values can be -- entered but function closures cannot). If you want a safe type to cast -- things to, use Any, which is not an algebraic data type. unsafeCoerce :: a -> b unsafeCoerceUnlifted :: forall (a :: UnliftedType) (b :: UnliftedType). a -> b unsafeCoerceAddr :: forall (a :: TYPE 'AddrRep) (b :: TYPE 'AddrRep). a -> b unsafeEqualityProof :: forall {k} (a :: k) (b :: k). UnsafeEquality a b -- | This type is treated magically within GHC. Any pattern match of the -- form case unsafeEqualityProof of UnsafeRefl -> body gets -- transformed just into body. This is ill-typed, but the -- transformation takes place after type-checking is complete. It is used -- to implement unsafeCoerce. You probably don't want to use -- UnsafeRefl in an expression, but you might conceivably want to -- pattern-match on it. Use unsafeEqualityProof to create one of -- these. data UnsafeEquality (a :: k) (b :: k) [UnsafeRefl] :: forall {k} (a :: k). UnsafeEquality a a -- | Highly, terribly dangerous coercion from one representation type to -- another. Misuse of this function can invite the garbage collector to -- trounce upon your data and then laugh in your face. You don't want -- this function. Really. unsafeCoerce# :: a -> b -- | Stable pointers. module GHC.Stable -- | 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. -- -- The StablePtr 0 is reserved for representing NULL in foreign -- code. -- -- A value of type StablePtr a is a stable pointer to a Haskell -- expression of type a. data StablePtr a StablePtr :: StablePtr# a -> 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 -- newStablePtr. 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 -- might 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 instance GHC.Classes.Eq (GHC.Stable.StablePtr a) -- | Helper functions for Foreign.Storable module GHC.Storable readWideCharOffPtr :: Ptr Char -> Int -> IO Char readIntOffPtr :: Ptr Int -> Int -> IO Int readWordOffPtr :: Ptr Word -> Int -> IO Word readPtrOffPtr :: Ptr (Ptr a) -> Int -> IO (Ptr a) readFunPtrOffPtr :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) readFloatOffPtr :: Ptr Float -> Int -> IO Float readDoubleOffPtr :: Ptr Double -> Int -> IO Double readStablePtrOffPtr :: Ptr (StablePtr a) -> Int -> IO (StablePtr a) readInt8OffPtr :: Ptr Int8 -> Int -> IO Int8 readInt16OffPtr :: Ptr Int16 -> Int -> IO Int16 readInt32OffPtr :: Ptr Int32 -> Int -> IO Int32 readInt64OffPtr :: Ptr Int64 -> Int -> IO Int64 readWord8OffPtr :: Ptr Word8 -> Int -> IO Word8 readWord16OffPtr :: Ptr Word16 -> Int -> IO Word16 readWord32OffPtr :: Ptr Word32 -> Int -> IO Word32 readWord64OffPtr :: Ptr Word64 -> Int -> IO Word64 writeWideCharOffPtr :: Ptr Char -> Int -> Char -> IO () writeIntOffPtr :: Ptr Int -> Int -> Int -> IO () writeWordOffPtr :: Ptr Word -> Int -> Word -> IO () writePtrOffPtr :: Ptr (Ptr a) -> Int -> Ptr a -> IO () writeFunPtrOffPtr :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () writeFloatOffPtr :: Ptr Float -> Int -> Float -> IO () writeDoubleOffPtr :: Ptr Double -> Int -> Double -> IO () writeStablePtrOffPtr :: Ptr (StablePtr a) -> Int -> StablePtr a -> IO () writeInt8OffPtr :: Ptr Int8 -> Int -> Int8 -> IO () writeInt16OffPtr :: Ptr Int16 -> Int -> Int16 -> IO () writeInt32OffPtr :: Ptr Int32 -> Int -> Int32 -> IO () writeInt64OffPtr :: Ptr Int64 -> Int -> Int64 -> IO () writeWord8OffPtr :: Ptr Word8 -> Int -> Word8 -> IO () writeWord16OffPtr :: Ptr Word16 -> Int -> Word16 -> IO () writeWord32OffPtr :: Ptr Word32 -> Int -> Word32 -> IO () writeWord64OffPtr :: Ptr Word64 -> Int -> Word64 -> IO () -- | 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 alignment must be a power of two if this instance is -- to be used with alloca or allocaArray. 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 GHC.Types.Bool instance Foreign.Storable.Storable GHC.Types.Char instance Foreign.Storable.Storable (Foreign.C.ConstPtr.ConstPtr a) instance Foreign.Storable.Storable GHC.Types.Double instance Foreign.Storable.Storable GHC.Fingerprint.Type.Fingerprint instance Foreign.Storable.Storable GHC.Types.Float instance Foreign.Storable.Storable (GHC.Ptr.FunPtr a) instance Foreign.Storable.Storable GHC.Types.Int 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 GHC.Int.Int8 instance Foreign.Storable.Storable (GHC.Ptr.Ptr a) instance (Foreign.Storable.Storable a, GHC.Real.Integral a) => Foreign.Storable.Storable (GHC.Real.Ratio a) instance Foreign.Storable.Storable (GHC.Stable.StablePtr a) instance Foreign.Storable.Storable () instance Foreign.Storable.Storable GHC.Types.Word 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.Word.Word8 -- | 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.Bits.Bits Foreign.Ptr.IntPtr instance GHC.Bits.Bits Foreign.Ptr.WordPtr instance GHC.Enum.Bounded Foreign.Ptr.IntPtr instance GHC.Enum.Bounded Foreign.Ptr.WordPtr instance GHC.Enum.Enum Foreign.Ptr.IntPtr instance GHC.Enum.Enum Foreign.Ptr.WordPtr instance GHC.Classes.Eq Foreign.Ptr.IntPtr instance GHC.Classes.Eq Foreign.Ptr.WordPtr instance GHC.Bits.FiniteBits Foreign.Ptr.IntPtr instance GHC.Bits.FiniteBits Foreign.Ptr.WordPtr instance GHC.Real.Integral Foreign.Ptr.IntPtr instance GHC.Real.Integral Foreign.Ptr.WordPtr instance GHC.Ix.Ix Foreign.Ptr.IntPtr instance GHC.Ix.Ix Foreign.Ptr.WordPtr instance GHC.Num.Num Foreign.Ptr.IntPtr instance GHC.Num.Num Foreign.Ptr.WordPtr instance GHC.Classes.Ord Foreign.Ptr.IntPtr instance GHC.Classes.Ord Foreign.Ptr.WordPtr instance GHC.Read.Read Foreign.Ptr.IntPtr instance GHC.Read.Read Foreign.Ptr.WordPtr instance GHC.Real.Real Foreign.Ptr.IntPtr instance GHC.Real.Real Foreign.Ptr.WordPtr instance GHC.Show.Show Foreign.Ptr.IntPtr instance GHC.Show.Show Foreign.Ptr.WordPtr instance Foreign.Storable.Storable Foreign.Ptr.IntPtr instance Foreign.Storable.Storable Foreign.Ptr.WordPtr -- | Mapping of C types to corresponding Haskell types. module Foreign.C.Types -- | Haskell type representing the C char type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) newtype CChar CChar :: Int8 -> CChar -- | Haskell type representing the C signed char type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CSChar CSChar :: Int8 -> CSChar -- | Haskell type representing the C unsigned char type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CUChar CUChar :: Word8 -> CUChar -- | Haskell type representing the C short type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) newtype CShort CShort :: Int16 -> CShort -- | Haskell type representing the C unsigned short type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CUShort CUShort :: Word16 -> CUShort -- | Haskell type representing the C int type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) newtype CInt CInt :: Int32 -> CInt -- | Haskell type representing the C unsigned int type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CUInt CUInt :: Word32 -> CUInt -- | Haskell type representing the C long type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) newtype CLong CLong :: Int64 -> CLong -- | Haskell type representing the C unsigned long type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CULong CULong :: Word64 -> CULong -- | Haskell type representing the C ptrdiff_t type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CPtrdiff CPtrdiff :: Int64 -> CPtrdiff -- | Haskell type representing the C size_t type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) newtype CSize CSize :: Word64 -> CSize -- | Haskell type representing the C wchar_t type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CWchar CWchar :: Int32 -> CWchar -- | Haskell type representing the C sig_atomic_t type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) See Note [Lack of signals on wasm32-wasi]. newtype CSigAtomic CSigAtomic :: Int32 -> CSigAtomic -- | Haskell type representing the C long long type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CLLong CLLong :: Int64 -> CLLong -- | Haskell type representing the C unsigned long long type. -- (The concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CULLong CULLong :: Word64 -> CULLong -- | Haskell type representing the C bool type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) newtype 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. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CClock CClock :: Int64 -> CClock -- | Haskell type representing the C time_t type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) newtype CTime CTime :: Int64 -> CTime -- | Haskell type representing the C useconds_t type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CUSeconds CUSeconds :: Word32 -> CUSeconds -- | Haskell type representing the C suseconds_t type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) newtype CSUSeconds CSUSeconds :: Int64 -> CSUSeconds -- | Haskell type representing the C float type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) newtype CFloat CFloat :: Float -> CFloat -- | Haskell type representing the C double type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) newtype CDouble CDouble :: Double -> CDouble -- | Haskell type representing the C FILE type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) data CFile -- | Haskell type representing the C fpos_t type. (The concrete -- types of Foreign.C.Types#platform are platform-specific.) data CFpos -- | Haskell type representing the C jmp_buf type. (The -- concrete types of Foreign.C.Types#platform are -- platform-specific.) data CJmpBuf instance GHC.Bits.Bits Foreign.C.Types.CBool instance GHC.Bits.Bits Foreign.C.Types.CChar instance GHC.Bits.Bits Foreign.C.Types.CInt instance GHC.Bits.Bits Foreign.C.Types.CIntMax instance GHC.Bits.Bits Foreign.C.Types.CIntPtr instance GHC.Bits.Bits Foreign.C.Types.CLLong instance GHC.Bits.Bits Foreign.C.Types.CLong instance GHC.Bits.Bits Foreign.C.Types.CPtrdiff instance GHC.Bits.Bits Foreign.C.Types.CSChar instance GHC.Bits.Bits Foreign.C.Types.CShort instance GHC.Bits.Bits Foreign.C.Types.CSigAtomic instance GHC.Bits.Bits Foreign.C.Types.CSize instance GHC.Bits.Bits Foreign.C.Types.CUChar instance GHC.Bits.Bits Foreign.C.Types.CUInt instance GHC.Bits.Bits Foreign.C.Types.CUIntMax instance GHC.Bits.Bits Foreign.C.Types.CUIntPtr instance GHC.Bits.Bits Foreign.C.Types.CULLong instance GHC.Bits.Bits Foreign.C.Types.CULong instance GHC.Bits.Bits Foreign.C.Types.CUShort instance GHC.Bits.Bits Foreign.C.Types.CWchar instance GHC.Enum.Bounded Foreign.C.Types.CBool instance GHC.Enum.Bounded Foreign.C.Types.CChar instance GHC.Enum.Bounded Foreign.C.Types.CInt instance GHC.Enum.Bounded Foreign.C.Types.CIntMax instance GHC.Enum.Bounded Foreign.C.Types.CIntPtr instance GHC.Enum.Bounded Foreign.C.Types.CLLong instance GHC.Enum.Bounded Foreign.C.Types.CLong instance GHC.Enum.Bounded Foreign.C.Types.CPtrdiff instance GHC.Enum.Bounded Foreign.C.Types.CSChar instance GHC.Enum.Bounded Foreign.C.Types.CShort instance GHC.Enum.Bounded Foreign.C.Types.CSigAtomic instance GHC.Enum.Bounded Foreign.C.Types.CSize instance GHC.Enum.Bounded Foreign.C.Types.CUChar instance GHC.Enum.Bounded Foreign.C.Types.CUInt instance GHC.Enum.Bounded Foreign.C.Types.CUIntMax instance GHC.Enum.Bounded Foreign.C.Types.CUIntPtr instance GHC.Enum.Bounded Foreign.C.Types.CULLong instance GHC.Enum.Bounded Foreign.C.Types.CULong instance GHC.Enum.Bounded Foreign.C.Types.CUShort instance GHC.Enum.Bounded Foreign.C.Types.CWchar instance GHC.Enum.Enum Foreign.C.Types.CBool instance GHC.Enum.Enum Foreign.C.Types.CChar instance GHC.Enum.Enum Foreign.C.Types.CClock instance GHC.Enum.Enum Foreign.C.Types.CDouble instance GHC.Enum.Enum Foreign.C.Types.CFloat instance GHC.Enum.Enum Foreign.C.Types.CInt instance GHC.Enum.Enum Foreign.C.Types.CIntMax instance GHC.Enum.Enum Foreign.C.Types.CIntPtr instance GHC.Enum.Enum Foreign.C.Types.CLLong instance GHC.Enum.Enum Foreign.C.Types.CLong instance GHC.Enum.Enum Foreign.C.Types.CPtrdiff instance GHC.Enum.Enum Foreign.C.Types.CSChar instance GHC.Enum.Enum Foreign.C.Types.CSUSeconds instance GHC.Enum.Enum Foreign.C.Types.CShort instance GHC.Enum.Enum Foreign.C.Types.CSigAtomic instance GHC.Enum.Enum Foreign.C.Types.CSize instance GHC.Enum.Enum Foreign.C.Types.CTime instance GHC.Enum.Enum Foreign.C.Types.CUChar instance GHC.Enum.Enum Foreign.C.Types.CUInt instance GHC.Enum.Enum Foreign.C.Types.CUIntMax instance GHC.Enum.Enum Foreign.C.Types.CUIntPtr instance GHC.Enum.Enum Foreign.C.Types.CULLong instance GHC.Enum.Enum Foreign.C.Types.CULong instance GHC.Enum.Enum Foreign.C.Types.CUSeconds instance GHC.Enum.Enum Foreign.C.Types.CUShort instance GHC.Enum.Enum Foreign.C.Types.CWchar instance GHC.Classes.Eq Foreign.C.Types.CBool instance GHC.Classes.Eq Foreign.C.Types.CChar instance GHC.Classes.Eq Foreign.C.Types.CClock instance GHC.Classes.Eq Foreign.C.Types.CDouble instance GHC.Classes.Eq Foreign.C.Types.CFloat instance GHC.Classes.Eq Foreign.C.Types.CInt instance GHC.Classes.Eq Foreign.C.Types.CIntMax instance GHC.Classes.Eq Foreign.C.Types.CIntPtr instance GHC.Classes.Eq Foreign.C.Types.CLLong instance GHC.Classes.Eq Foreign.C.Types.CLong instance GHC.Classes.Eq Foreign.C.Types.CPtrdiff instance GHC.Classes.Eq Foreign.C.Types.CSChar instance GHC.Classes.Eq Foreign.C.Types.CSUSeconds instance GHC.Classes.Eq Foreign.C.Types.CShort instance GHC.Classes.Eq Foreign.C.Types.CSigAtomic instance GHC.Classes.Eq Foreign.C.Types.CSize instance GHC.Classes.Eq Foreign.C.Types.CTime instance GHC.Classes.Eq Foreign.C.Types.CUChar instance GHC.Classes.Eq Foreign.C.Types.CUInt instance GHC.Classes.Eq Foreign.C.Types.CUIntMax instance GHC.Classes.Eq Foreign.C.Types.CUIntPtr instance GHC.Classes.Eq Foreign.C.Types.CULLong instance GHC.Classes.Eq Foreign.C.Types.CULong instance GHC.Classes.Eq Foreign.C.Types.CUSeconds instance GHC.Classes.Eq Foreign.C.Types.CUShort instance GHC.Classes.Eq Foreign.C.Types.CWchar instance GHC.Bits.FiniteBits Foreign.C.Types.CBool instance GHC.Bits.FiniteBits Foreign.C.Types.CChar instance GHC.Bits.FiniteBits Foreign.C.Types.CInt instance GHC.Bits.FiniteBits Foreign.C.Types.CIntMax instance GHC.Bits.FiniteBits Foreign.C.Types.CIntPtr instance GHC.Bits.FiniteBits Foreign.C.Types.CLLong instance GHC.Bits.FiniteBits Foreign.C.Types.CLong instance GHC.Bits.FiniteBits Foreign.C.Types.CPtrdiff instance GHC.Bits.FiniteBits Foreign.C.Types.CSChar instance GHC.Bits.FiniteBits Foreign.C.Types.CShort instance GHC.Bits.FiniteBits Foreign.C.Types.CSigAtomic instance GHC.Bits.FiniteBits Foreign.C.Types.CSize instance GHC.Bits.FiniteBits Foreign.C.Types.CUChar instance GHC.Bits.FiniteBits Foreign.C.Types.CUInt instance GHC.Bits.FiniteBits Foreign.C.Types.CUIntMax instance GHC.Bits.FiniteBits Foreign.C.Types.CUIntPtr instance GHC.Bits.FiniteBits Foreign.C.Types.CULLong instance GHC.Bits.FiniteBits Foreign.C.Types.CULong instance GHC.Bits.FiniteBits Foreign.C.Types.CUShort instance GHC.Bits.FiniteBits Foreign.C.Types.CWchar instance GHC.Float.Floating Foreign.C.Types.CDouble instance GHC.Float.Floating Foreign.C.Types.CFloat instance GHC.Real.Fractional Foreign.C.Types.CDouble instance GHC.Real.Fractional Foreign.C.Types.CFloat instance GHC.Real.Integral Foreign.C.Types.CBool instance GHC.Real.Integral Foreign.C.Types.CChar instance GHC.Real.Integral Foreign.C.Types.CInt instance GHC.Real.Integral Foreign.C.Types.CIntMax instance GHC.Real.Integral Foreign.C.Types.CIntPtr instance GHC.Real.Integral Foreign.C.Types.CLLong instance GHC.Real.Integral Foreign.C.Types.CLong instance GHC.Real.Integral Foreign.C.Types.CPtrdiff instance GHC.Real.Integral Foreign.C.Types.CSChar instance GHC.Real.Integral Foreign.C.Types.CShort instance GHC.Real.Integral Foreign.C.Types.CSigAtomic instance GHC.Real.Integral Foreign.C.Types.CSize instance GHC.Real.Integral Foreign.C.Types.CUChar instance GHC.Real.Integral Foreign.C.Types.CUInt instance GHC.Real.Integral Foreign.C.Types.CUIntMax instance GHC.Real.Integral Foreign.C.Types.CUIntPtr instance GHC.Real.Integral Foreign.C.Types.CULLong instance GHC.Real.Integral Foreign.C.Types.CULong instance GHC.Real.Integral Foreign.C.Types.CUShort instance GHC.Real.Integral Foreign.C.Types.CWchar instance GHC.Ix.Ix Foreign.C.Types.CBool instance GHC.Ix.Ix Foreign.C.Types.CChar instance GHC.Ix.Ix Foreign.C.Types.CInt instance GHC.Ix.Ix Foreign.C.Types.CIntMax instance GHC.Ix.Ix Foreign.C.Types.CIntPtr instance GHC.Ix.Ix Foreign.C.Types.CLLong instance GHC.Ix.Ix Foreign.C.Types.CLong instance GHC.Ix.Ix Foreign.C.Types.CPtrdiff instance GHC.Ix.Ix Foreign.C.Types.CSChar instance GHC.Ix.Ix Foreign.C.Types.CShort instance GHC.Ix.Ix Foreign.C.Types.CSigAtomic instance GHC.Ix.Ix Foreign.C.Types.CSize instance GHC.Ix.Ix Foreign.C.Types.CUChar instance GHC.Ix.Ix Foreign.C.Types.CUInt instance GHC.Ix.Ix Foreign.C.Types.CUIntMax instance GHC.Ix.Ix Foreign.C.Types.CUIntPtr instance GHC.Ix.Ix Foreign.C.Types.CULLong instance GHC.Ix.Ix Foreign.C.Types.CULong instance GHC.Ix.Ix Foreign.C.Types.CUShort instance GHC.Ix.Ix Foreign.C.Types.CWchar instance GHC.Num.Num Foreign.C.Types.CBool instance GHC.Num.Num Foreign.C.Types.CChar instance GHC.Num.Num Foreign.C.Types.CClock instance GHC.Num.Num Foreign.C.Types.CDouble instance GHC.Num.Num Foreign.C.Types.CFloat instance GHC.Num.Num Foreign.C.Types.CInt instance GHC.Num.Num Foreign.C.Types.CIntMax instance GHC.Num.Num Foreign.C.Types.CIntPtr instance GHC.Num.Num Foreign.C.Types.CLLong instance GHC.Num.Num Foreign.C.Types.CLong instance GHC.Num.Num Foreign.C.Types.CPtrdiff instance GHC.Num.Num Foreign.C.Types.CSChar instance GHC.Num.Num Foreign.C.Types.CSUSeconds instance GHC.Num.Num Foreign.C.Types.CShort instance GHC.Num.Num Foreign.C.Types.CSigAtomic instance GHC.Num.Num Foreign.C.Types.CSize instance GHC.Num.Num Foreign.C.Types.CTime instance GHC.Num.Num Foreign.C.Types.CUChar instance GHC.Num.Num Foreign.C.Types.CUInt instance GHC.Num.Num Foreign.C.Types.CUIntMax instance GHC.Num.Num Foreign.C.Types.CUIntPtr instance GHC.Num.Num Foreign.C.Types.CULLong instance GHC.Num.Num Foreign.C.Types.CULong instance GHC.Num.Num Foreign.C.Types.CUSeconds instance GHC.Num.Num Foreign.C.Types.CUShort instance GHC.Num.Num Foreign.C.Types.CWchar instance GHC.Classes.Ord Foreign.C.Types.CBool instance GHC.Classes.Ord Foreign.C.Types.CChar instance GHC.Classes.Ord Foreign.C.Types.CClock instance GHC.Classes.Ord Foreign.C.Types.CDouble instance GHC.Classes.Ord Foreign.C.Types.CFloat instance GHC.Classes.Ord Foreign.C.Types.CInt instance GHC.Classes.Ord Foreign.C.Types.CIntMax instance GHC.Classes.Ord Foreign.C.Types.CIntPtr instance GHC.Classes.Ord Foreign.C.Types.CLLong instance GHC.Classes.Ord Foreign.C.Types.CLong instance GHC.Classes.Ord Foreign.C.Types.CPtrdiff instance GHC.Classes.Ord Foreign.C.Types.CSChar instance GHC.Classes.Ord Foreign.C.Types.CSUSeconds instance GHC.Classes.Ord Foreign.C.Types.CShort instance GHC.Classes.Ord Foreign.C.Types.CSigAtomic instance GHC.Classes.Ord Foreign.C.Types.CSize instance GHC.Classes.Ord Foreign.C.Types.CTime instance GHC.Classes.Ord Foreign.C.Types.CUChar instance GHC.Classes.Ord Foreign.C.Types.CUInt instance GHC.Classes.Ord Foreign.C.Types.CUIntMax instance GHC.Classes.Ord Foreign.C.Types.CUIntPtr instance GHC.Classes.Ord Foreign.C.Types.CULLong instance GHC.Classes.Ord Foreign.C.Types.CULong instance GHC.Classes.Ord Foreign.C.Types.CUSeconds instance GHC.Classes.Ord Foreign.C.Types.CUShort instance GHC.Classes.Ord Foreign.C.Types.CWchar instance GHC.Read.Read Foreign.C.Types.CBool instance GHC.Read.Read Foreign.C.Types.CChar instance GHC.Read.Read Foreign.C.Types.CClock instance GHC.Read.Read Foreign.C.Types.CDouble instance GHC.Read.Read Foreign.C.Types.CFloat instance GHC.Read.Read Foreign.C.Types.CInt instance GHC.Read.Read Foreign.C.Types.CIntMax instance GHC.Read.Read Foreign.C.Types.CIntPtr instance GHC.Read.Read Foreign.C.Types.CLLong instance GHC.Read.Read Foreign.C.Types.CLong instance GHC.Read.Read Foreign.C.Types.CPtrdiff instance GHC.Read.Read Foreign.C.Types.CSChar instance GHC.Read.Read Foreign.C.Types.CSUSeconds instance GHC.Read.Read Foreign.C.Types.CShort instance GHC.Read.Read Foreign.C.Types.CSigAtomic instance GHC.Read.Read Foreign.C.Types.CSize instance GHC.Read.Read Foreign.C.Types.CTime instance GHC.Read.Read Foreign.C.Types.CUChar instance GHC.Read.Read Foreign.C.Types.CUInt instance GHC.Read.Read Foreign.C.Types.CUIntMax instance GHC.Read.Read Foreign.C.Types.CUIntPtr instance GHC.Read.Read Foreign.C.Types.CULLong instance GHC.Read.Read Foreign.C.Types.CULong instance GHC.Read.Read Foreign.C.Types.CUSeconds instance GHC.Read.Read Foreign.C.Types.CUShort instance GHC.Read.Read Foreign.C.Types.CWchar instance GHC.Real.Real Foreign.C.Types.CBool instance GHC.Real.Real Foreign.C.Types.CChar instance GHC.Real.Real Foreign.C.Types.CClock instance GHC.Real.Real Foreign.C.Types.CDouble instance GHC.Real.Real Foreign.C.Types.CFloat instance GHC.Real.Real Foreign.C.Types.CInt instance GHC.Real.Real Foreign.C.Types.CIntMax instance GHC.Real.Real Foreign.C.Types.CIntPtr instance GHC.Real.Real Foreign.C.Types.CLLong instance GHC.Real.Real Foreign.C.Types.CLong instance GHC.Real.Real Foreign.C.Types.CPtrdiff instance GHC.Real.Real Foreign.C.Types.CSChar instance GHC.Real.Real Foreign.C.Types.CSUSeconds instance GHC.Real.Real Foreign.C.Types.CShort instance GHC.Real.Real Foreign.C.Types.CSigAtomic instance GHC.Real.Real Foreign.C.Types.CSize instance GHC.Real.Real Foreign.C.Types.CTime instance GHC.Real.Real Foreign.C.Types.CUChar instance GHC.Real.Real Foreign.C.Types.CUInt instance GHC.Real.Real Foreign.C.Types.CUIntMax instance GHC.Real.Real Foreign.C.Types.CUIntPtr instance GHC.Real.Real Foreign.C.Types.CULLong instance GHC.Real.Real Foreign.C.Types.CULong instance GHC.Real.Real Foreign.C.Types.CUSeconds instance GHC.Real.Real Foreign.C.Types.CUShort instance GHC.Real.Real Foreign.C.Types.CWchar instance GHC.Float.RealFloat Foreign.C.Types.CDouble instance GHC.Float.RealFloat Foreign.C.Types.CFloat instance GHC.Real.RealFrac Foreign.C.Types.CDouble instance GHC.Real.RealFrac Foreign.C.Types.CFloat instance GHC.Show.Show Foreign.C.Types.CBool instance GHC.Show.Show Foreign.C.Types.CChar instance GHC.Show.Show Foreign.C.Types.CClock instance GHC.Show.Show Foreign.C.Types.CDouble instance GHC.Show.Show Foreign.C.Types.CFloat instance GHC.Show.Show Foreign.C.Types.CInt instance GHC.Show.Show Foreign.C.Types.CIntMax instance GHC.Show.Show Foreign.C.Types.CIntPtr instance GHC.Show.Show Foreign.C.Types.CLLong instance GHC.Show.Show Foreign.C.Types.CLong instance GHC.Show.Show Foreign.C.Types.CPtrdiff instance GHC.Show.Show Foreign.C.Types.CSChar instance GHC.Show.Show Foreign.C.Types.CSUSeconds instance GHC.Show.Show Foreign.C.Types.CShort instance GHC.Show.Show Foreign.C.Types.CSigAtomic instance GHC.Show.Show Foreign.C.Types.CSize instance GHC.Show.Show Foreign.C.Types.CTime instance GHC.Show.Show Foreign.C.Types.CUChar instance GHC.Show.Show Foreign.C.Types.CUInt instance GHC.Show.Show Foreign.C.Types.CUIntMax instance GHC.Show.Show Foreign.C.Types.CUIntPtr instance GHC.Show.Show Foreign.C.Types.CULLong instance GHC.Show.Show Foreign.C.Types.CULong instance GHC.Show.Show Foreign.C.Types.CUSeconds instance GHC.Show.Show Foreign.C.Types.CUShort instance GHC.Show.Show Foreign.C.Types.CWchar instance Foreign.Storable.Storable Foreign.C.Types.CBool instance Foreign.Storable.Storable Foreign.C.Types.CChar instance Foreign.Storable.Storable Foreign.C.Types.CClock instance Foreign.Storable.Storable Foreign.C.Types.CDouble instance Foreign.Storable.Storable Foreign.C.Types.CFloat instance Foreign.Storable.Storable Foreign.C.Types.CInt instance Foreign.Storable.Storable Foreign.C.Types.CIntMax instance Foreign.Storable.Storable Foreign.C.Types.CIntPtr instance Foreign.Storable.Storable Foreign.C.Types.CLLong instance Foreign.Storable.Storable Foreign.C.Types.CLong instance Foreign.Storable.Storable Foreign.C.Types.CPtrdiff instance Foreign.Storable.Storable Foreign.C.Types.CSChar instance Foreign.Storable.Storable Foreign.C.Types.CSUSeconds instance Foreign.Storable.Storable Foreign.C.Types.CShort instance Foreign.Storable.Storable Foreign.C.Types.CSigAtomic instance Foreign.Storable.Storable Foreign.C.Types.CSize instance Foreign.Storable.Storable Foreign.C.Types.CTime instance Foreign.Storable.Storable Foreign.C.Types.CUChar instance Foreign.Storable.Storable Foreign.C.Types.CUInt instance Foreign.Storable.Storable Foreign.C.Types.CUIntMax instance Foreign.Storable.Storable Foreign.C.Types.CUIntPtr instance Foreign.Storable.Storable Foreign.C.Types.CULLong instance Foreign.Storable.Storable Foreign.C.Types.CULong instance Foreign.Storable.Storable Foreign.C.Types.CUSeconds instance Foreign.Storable.Storable Foreign.C.Types.CUShort instance Foreign.Storable.Storable Foreign.C.Types.CWchar -- | 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. -- -- Ord, as defined by the Haskell report, implements a total order -- and has the following properties: -- -- -- -- The following operator interactions are expected to hold: -- --
    --
  1. x >= y = y <= x
  2. --
  3. x < y = x <= y && x /= y
  4. --
  5. x > y = y < x
  6. --
  7. x < y = compare x y == LT
  8. --
  9. x > y = compare x y == GT
  10. --
  11. x == y = compare x y == EQ
  12. --
  13. min x y == if x <= y then x else y = True
  14. --
  15. max x y == if x >= y then x else y = True
  16. --
-- -- Note that (7.) and (8.) do not require min and -- max to return either of their arguments. The result is merely -- required to equal one of the arguments in terms of (==). -- -- 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 infix 4 >= infix 4 < infix 4 <= infix 4 > 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. -- --
--   >>> compare True False
--   GT
--   
-- --
--   >>> compare (Down True) (Down False)
--   LT
--   
-- -- If a has a Bounded instance then the wrapped -- instance also respects the reversed ordering by exchanging the values -- of minBound and maxBound. -- --
--   >>> minBound :: Int
--   -9223372036854775808
--   
-- --
--   >>> minBound :: Down Int
--   Down 9223372036854775807
--   
-- -- All other instances of Down a behave as they do for -- a. newtype Down a Down :: a -> Down a [getDown] :: Down a -> 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 -- |
--   clamp (low, high) a = min high (max a low)
--   
-- -- Function for ensuring the value a is within the inclusive -- bounds given by low and high. If it is, a -- is returned unchanged. The result is otherwise low if a -- <= low, or high if high <= a. -- -- When clamp is used at Double and Float, it has NaN propagating -- semantics in its second argument. That is, clamp (l,h) NaN = -- NaN, but clamp (NaN, NaN) x = x. -- --
--   >>> clamp (0, 10) 2
--   2
--   
-- --
--   >>> clamp ('a', 'm') 'x'
--   'm'
--   
clamp :: Ord a => (a, a) -> a -> a instance GHC.Base.Applicative Data.Ord.Down instance GHC.Bits.Bits a => GHC.Bits.Bits (Data.Ord.Down a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Ord.Down a) instance (GHC.Enum.Enum a, GHC.Enum.Bounded a, GHC.Classes.Eq a) => GHC.Enum.Enum (Data.Ord.Down a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Ord.Down a) instance GHC.Bits.FiniteBits a => GHC.Bits.FiniteBits (Data.Ord.Down a) instance GHC.Float.Floating a => GHC.Float.Floating (Data.Ord.Down a) instance GHC.Real.Fractional a => GHC.Real.Fractional (Data.Ord.Down a) instance GHC.Base.Functor Data.Ord.Down instance GHC.Ix.Ix a => GHC.Ix.Ix (Data.Ord.Down a) instance GHC.Base.Monad Data.Ord.Down instance GHC.Base.Monoid a => GHC.Base.Monoid (Data.Ord.Down a) instance GHC.Num.Num a => GHC.Num.Num (Data.Ord.Down a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Ord.Down a) instance GHC.Read.Read a => GHC.Read.Read (Data.Ord.Down a) instance GHC.Real.Real a => GHC.Real.Real (Data.Ord.Down a) instance GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Ord.Down a) instance GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Ord.Down a) instance GHC.Base.Semigroup a => GHC.Base.Semigroup (Data.Ord.Down a) instance GHC.Show.Show a => GHC.Show.Show (Data.Ord.Down a) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Data.Ord.Down a) -- | Basic operations on type-level Orderings. module Data.Type.Ord -- | Compare branches on the kind of its arguments to either compare -- by Symbol or Nat. type family Compare (a :: k) (b :: k) :: Ordering -- | Ordering data type for type literals that provides proof of their -- ordering. data OrderingI (a :: k) (b :: k) [LTI] :: forall {k} (a :: k) (b :: k). Compare a b ~ 'LT => OrderingI a b [EQI] :: forall {k} (a :: k). Compare a a ~ 'EQ => OrderingI a a [GTI] :: forall {k} (a :: k) (b :: k). Compare a b ~ 'GT => OrderingI a b -- | Comparison (<=) of comparable types, as a constraint. type (x :: t) <= (y :: t) = Assert x <=? y LeErrMsg x y :: Constraint infix 4 <= -- | Comparison (<=) of comparable types, as a function. type (m :: k) <=? (n :: k) = OrdCond Compare m n 'True 'True 'False infix 4 <=? -- | Comparison (>=) of comparable types, as a constraint. type (x :: t) >= (y :: t) = Assert x >=? y GeErrMsg x y :: Constraint infix 4 >= -- | Comparison (>=) of comparable types, as a function. type (m :: k) >=? (n :: k) = OrdCond Compare m n 'False 'True 'True infix 4 >=? -- | Comparison (>) of comparable types, as a constraint. type (x :: t) > (y :: t) = Assert x >? y GtErrMsg x y :: Constraint infix 4 > -- | Comparison (>) of comparable types, as a function. type (m :: k) >? (n :: k) = OrdCond Compare m n 'False 'False 'True infix 4 >? -- | Comparison (<) of comparable types, as a constraint. type (x :: t) < (y :: t) = Assert x Ordering. -- -- OrdCond c l e g is l when c ~ LT, -- e when c ~ EQ, and g when c ~ GT. type family OrdCond (o :: Ordering) (lt :: k) (eq :: k) (gt :: k) :: k instance forall k (a :: k) (b :: k). GHC.Classes.Eq (Data.Type.Ord.OrderingI a b) instance forall k (a :: k) (b :: k). GHC.Show.Show (Data.Type.Ord.OrderingI 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 -- | Natural number -- -- Invariant: numbers <= 0xffffffffffffffff use the NS -- constructor data Natural -- | A type synonym for Natural. -- -- Previously, this was an opaque data type, but it was changed to a type -- synonym. type Nat = Natural -- | 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) natSing :: KnownNat n => SNat n natVal :: forall (n :: Nat) proxy. KnownNat n => proxy n -> Natural natVal' :: forall (n :: Nat). 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 :: forall (a :: Nat) (b :: Nat) proxy1 proxy2. (KnownNat a, KnownNat b) => proxy1 a -> proxy2 b -> Maybe (a :~: b) -- | We either get evidence that this function was instantiated with the -- same type-level numbers, or that the type-level numbers are distinct. decideNat :: forall (a :: Nat) (b :: Nat) proxy1 proxy2. (KnownNat a, KnownNat b) => proxy1 a -> proxy2 b -> Either ((a :~: b) -> Void) (a :~: b) -- | A value-level witness for a type-level natural number. This is -- commonly referred to as a singleton type, as for each -- n, there is a single value that inhabits the type -- SNat n (aside from bottom). -- -- The definition of SNat is intentionally left abstract. To -- obtain an SNat value, use one of the following: -- --
    --
  1. The natSing method of KnownNat.
  2. --
  3. The SNat pattern synonym.
  4. --
  5. The withSomeSNat function, which creates an SNat -- from a Natural number.
  6. --
data SNat (n :: Nat) -- | A explicitly bidirectional pattern synonym relating an SNat to -- a KnownNat constraint. -- -- As an expression: Constructs an explicit SNat n -- value from an implicit KnownNat n constraint: -- --
--   SNat @n :: KnownNat n => SNat n
--   
-- -- As a pattern: Matches on an explicit SNat n -- value bringing an implicit KnownNat n constraint into -- scope: -- --
--   f :: SNat n -> ..
--   f SNat = {- SNat n in scope -}
--   
pattern SNat :: () => KnownNat n => SNat n -- | Return the Natural number corresponding to n in an -- SNat n value. fromSNat :: forall (n :: Nat). SNat n -> Natural -- | Convert a Natural number into an SNat n value, -- where n is a fresh type-level natural number. withSomeSNat :: Natural -> (forall (n :: Nat). () => SNat n -> r) -> r -- | Convert an explicit SNat n value into an implicit -- KnownNat n constraint. withKnownNat :: forall (n :: Nat) r. SNat n -> (KnownNat n => r) -> r -- | Comparison (<=) of comparable types, as a constraint. type (x :: t) <= (y :: t) = Assert x <=? y LeErrMsg x y :: Constraint infix 4 <= -- | Comparison (<=) of comparable types, as a function. type (m :: k) <=? (n :: k) = OrdCond Compare m n 'True 'True 'False infix 4 <=? -- | Addition of type-level naturals. type family (a :: Natural) + (b :: Natural) :: Natural infixl 6 + -- | Multiplication of type-level naturals. type family (a :: Natural) * (b :: Natural) :: Natural infixl 7 * -- | Exponentiation of type-level naturals. type family (a :: Natural) ^ (b :: Natural) :: Natural infixr 8 ^ -- | Subtraction of type-level naturals. type family (a :: Natural) - (b :: Natural) :: Natural infixl 6 - -- | Comparison of type-level naturals, as a function. type family CmpNat (a :: Natural) (b :: Natural) :: Ordering -- | Like sameNat, but if the numbers aren't equal, this -- additionally provides proof of LT or GT. cmpNat :: forall (a :: Nat) (b :: Nat) proxy1 proxy2. (KnownNat a, KnownNat b) => proxy1 a -> proxy2 b -> OrderingI a b -- | Division (round down) of natural numbers. Div x 0 is -- undefined (i.e., it cannot be reduced). type family Div (a :: Natural) (b :: Natural) :: Natural infixl 7 `Div` -- | Modulus of natural numbers. Mod x 0 is undefined (i.e., it -- cannot be reduced). type family Mod (a :: Natural) (b :: Natural) :: Natural infixl 7 `Mod` -- | Log base 2 (round down) of natural numbers. Log 0 is -- undefined (i.e., it cannot be reduced). type family Log2 (a :: Natural) :: Natural instance GHC.Classes.Eq (GHC.TypeNats.SNat n) instance GHC.Classes.Eq GHC.TypeNats.SomeNat instance GHC.Classes.Ord (GHC.TypeNats.SNat n) instance GHC.Classes.Ord GHC.TypeNats.SomeNat instance GHC.Read.Read GHC.TypeNats.SomeNat instance GHC.Show.Show (GHC.TypeNats.SNat n) instance GHC.Show.Show GHC.TypeNats.SomeNat instance Data.Type.Coercion.TestCoercion GHC.TypeNats.SNat instance Data.Type.Equality.TestEquality GHC.TypeNats.SNat -- | GHC's DataKinds language extension lifts data constructors, -- natural numbers, and strings to the type level. This module provides -- the primitives needed for working with type-level numbers (the -- Nat kind), strings (the Symbol kind), and characters -- (the Char kind). It also defines the TypeError type -- family, a feature that makes use of type-level strings to support user -- defined type errors. -- -- For now, this module is the API for working with type-level literals. -- However, please note that it is a work in progress and is subject to -- change. Once the design of the DataKinds feature is more -- stable, this will be considered only an internal GHC module, and the -- programmer interface for working with type-level data will be defined -- in a separate library. module GHC.TypeLits -- | Natural number -- -- Invariant: numbers <= 0xffffffffffffffff use the NS -- constructor data Natural -- | A type synonym for Natural. -- -- Previously, this was an opaque data type, but it was changed to a type -- synonym. type Nat = Natural -- | (Kind) This is the kind of type-level symbols. 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) natSing :: KnownNat n => SNat n natVal :: forall (n :: Nat) proxy. KnownNat n => proxy n -> Integer natVal' :: forall (n :: Nat). 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) symbolSing :: KnownSymbol n => SSymbol n symbolVal :: forall (n :: Symbol) proxy. KnownSymbol n => proxy n -> String symbolVal' :: forall (n :: Symbol). KnownSymbol n => Proxy# n -> String class KnownChar (n :: Char) charSing :: KnownChar n => SChar n charVal :: forall (n :: Char) proxy. KnownChar n => proxy n -> Char charVal' :: forall (n :: Char). KnownChar n => Proxy# n -> Char -- | 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 data SomeChar SomeChar :: Proxy n -> SomeChar -- | 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 -- | Convert a character into an unknown type-level char. someCharVal :: Char -> SomeChar -- | We either get evidence that this function was instantiated with the -- same type-level numbers, or Nothing. sameNat :: forall (a :: Nat) (b :: Nat) proxy1 proxy2. (KnownNat a, KnownNat b) => proxy1 a -> proxy2 b -> Maybe (a :~: b) -- | We either get evidence that this function was instantiated with the -- same type-level symbols, or Nothing. sameSymbol :: forall (a :: Symbol) (b :: Symbol) proxy1 proxy2. (KnownSymbol a, KnownSymbol b) => proxy1 a -> proxy2 b -> Maybe (a :~: b) -- | We either get evidence that this function was instantiated with the -- same type-level characters, or Nothing. sameChar :: forall (a :: Char) (b :: Char) proxy1 proxy2. (KnownChar a, KnownChar b) => proxy1 a -> proxy2 b -> Maybe (a :~: b) -- | We either get evidence that this function was instantiated with the -- same type-level numbers, or that the type-level numbers are distinct. decideNat :: forall (a :: Nat) (b :: Nat) proxy1 proxy2. (KnownNat a, KnownNat b) => proxy1 a -> proxy2 b -> Either ((a :~: b) -> Void) (a :~: b) -- | We either get evidence that this function was instantiated with the -- same type-level symbols, or that the type-level symbols are distinct. decideSymbol :: forall (a :: Symbol) (b :: Symbol) proxy1 proxy2. (KnownSymbol a, KnownSymbol b) => proxy1 a -> proxy2 b -> Either ((a :~: b) -> Void) (a :~: b) -- | We either get evidence that this function was instantiated with the -- same type-level characters, or that the type-level characters are -- distinct. decideChar :: forall (a :: Char) (b :: Char) proxy1 proxy2. (KnownChar a, KnownChar b) => proxy1 a -> proxy2 b -> Either ((a :~: b) -> Void) (a :~: b) -- | Ordering data type for type literals that provides proof of their -- ordering. data OrderingI (a :: k) (b :: k) [LTI] :: forall {k} (a :: k) (b :: k). Compare a b ~ 'LT => OrderingI a b [EQI] :: forall {k} (a :: k). Compare a a ~ 'EQ => OrderingI a a [GTI] :: forall {k} (a :: k) (b :: k). Compare a b ~ 'GT => OrderingI a b -- | Like sameNat, but if the numbers aren't equal, this -- additionally provides proof of LT or GT. cmpNat :: forall (a :: Nat) (b :: Nat) proxy1 proxy2. (KnownNat a, KnownNat b) => proxy1 a -> proxy2 b -> OrderingI a b -- | Like sameSymbol, but if the symbols aren't equal, this -- additionally provides proof of LT or GT. cmpSymbol :: forall (a :: Symbol) (b :: Symbol) proxy1 proxy2. (KnownSymbol a, KnownSymbol b) => proxy1 a -> proxy2 b -> OrderingI a b -- | Like sameChar, but if the Chars aren't equal, this additionally -- provides proof of LT or GT. cmpChar :: forall (a :: Char) (b :: Char) proxy1 proxy2. (KnownChar a, KnownChar b) => proxy1 a -> proxy2 b -> OrderingI a b -- | A value-level witness for a type-level natural number. This is -- commonly referred to as a singleton type, as for each -- n, there is a single value that inhabits the type -- SNat n (aside from bottom). -- -- The definition of SNat is intentionally left abstract. To -- obtain an SNat value, use one of the following: -- --
    --
  1. The natSing method of KnownNat.
  2. --
  3. The SNat pattern synonym.
  4. --
  5. The withSomeSNat function, which creates an SNat -- from a Natural number.
  6. --
data SNat (n :: Nat) -- | A value-level witness for a type-level symbol. This is commonly -- referred to as a singleton type, as for each s, there -- is a single value that inhabits the type SSymbol s -- (aside from bottom). -- -- The definition of SSymbol is intentionally left abstract. To -- obtain an SSymbol value, use one of the following: -- --
    --
  1. The symbolSing method of KnownSymbol.
  2. --
  3. The SSymbol pattern synonym.
  4. --
  5. The withSomeSSymbol function, which creates an -- SSymbol from a String.
  6. --
data SSymbol (s :: Symbol) -- | A value-level witness for a type-level character. This is commonly -- referred to as a singleton type, as for each c, there -- is a single value that inhabits the type SChar c -- (aside from bottom). -- -- The definition of SChar is intentionally left abstract. To -- obtain an SChar value, use one of the following: -- --
    --
  1. The charSing method of KnownChar.
  2. --
  3. The SChar pattern synonym.
  4. --
  5. The withSomeSChar function, which creates an SChar -- from a Char.
  6. --
data SChar (s :: Char) -- | A explicitly bidirectional pattern synonym relating an SNat to -- a KnownNat constraint. -- -- As an expression: Constructs an explicit SNat n -- value from an implicit KnownNat n constraint: -- --
--   SNat @n :: KnownNat n => SNat n
--   
-- -- As a pattern: Matches on an explicit SNat n -- value bringing an implicit KnownNat n constraint into -- scope: -- --
--   f :: SNat n -> ..
--   f SNat = {- SNat n in scope -}
--   
pattern SNat :: () => KnownNat n => SNat n -- | A explicitly bidirectional pattern synonym relating an SSymbol -- to a KnownSymbol constraint. -- -- As an expression: Constructs an explicit SSymbol -- s value from an implicit KnownSymbol s -- constraint: -- --
--   SSymbol @s :: KnownSymbol s => SSymbol s
--   
-- -- As a pattern: Matches on an explicit SSymbol s -- value bringing an implicit KnownSymbol s constraint -- into scope: -- --
--   f :: SSymbol s -> ..
--   f SSymbol = {- SSymbol s in scope -}
--   
pattern SSymbol :: () => KnownSymbol s => SSymbol s -- | A explicitly bidirectional pattern synonym relating an SChar to -- a KnownChar constraint. -- -- As an expression: Constructs an explicit SChar -- c value from an implicit KnownChar c constraint: -- --
--   SChar @c :: KnownChar c => SChar c
--   
-- -- As a pattern: Matches on an explicit SChar c -- value bringing an implicit KnownChar c constraint into -- scope: -- --
--   f :: SChar c -> ..
--   f SChar = {- SChar c in scope -}
--   
pattern SChar :: () => KnownChar c => SChar c -- | Return the Integer corresponding to n in an -- SNat n value. The returned Integer is always -- non-negative. -- -- For a version of this function that returns a Natural instead -- of an Integer, see fromSNat in GHC.TypeNats. fromSNat :: forall (n :: Nat). SNat n -> Integer -- | Return the String corresponding to s in an SSymbol -- s value. fromSSymbol :: forall (s :: Symbol). SSymbol s -> String -- | Return the Char corresponding to c in an -- SChar c value. fromSChar :: forall (c :: Char). SChar c -> Char -- | Attempt to convert an Integer into an SNat n -- value, where n is a fresh type-level natural number. If the -- Integer argument is non-negative, invoke the continuation with -- Just sn, where sn is the SNat n -- value. If the Integer argument is negative, invoke the -- continuation with Nothing. -- -- For a version of this function where the continuation uses -- 'SNat n instead of Maybe (SNat n)@, -- see withSomeSNat in GHC.TypeNats. withSomeSNat :: Integer -> (forall (n :: Nat). () => Maybe (SNat n) -> r) -> r -- | Convert a String into an SSymbol s value, where -- s is a fresh type-level symbol. withSomeSSymbol :: String -> (forall (s :: Symbol). () => SSymbol s -> r) -> r -- | Convert a Char into an SChar c value, where -- c is a fresh type-level character. withSomeSChar :: Char -> (forall (c :: Char). () => SChar c -> r) -> r -- | Convert an explicit SNat n value into an implicit -- KnownNat n constraint. withKnownNat :: forall (n :: Nat) r. SNat n -> (KnownNat n => r) -> r -- | Convert an explicit SSymbol s value into an implicit -- KnownSymbol s constraint. withKnownSymbol :: forall (s :: Symbol) r. SSymbol s -> (KnownSymbol s => r) -> r -- | Convert an explicit SChar c value into an implicit -- KnownChar c constraint. withKnownChar :: forall (c :: Char) r. SChar c -> (KnownChar c => r) -> r -- | Comparison (<=) of comparable types, as a constraint. type (x :: t) <= (y :: t) = Assert x <=? y LeErrMsg x y :: Constraint infix 4 <= -- | Comparison (<=) of comparable types, as a function. type (m :: k) <=? (n :: k) = OrdCond Compare m n 'True 'True 'False infix 4 <=? -- | Addition of type-level naturals. type family (a :: Natural) + (b :: Natural) :: Natural infixl 6 + -- | Multiplication of type-level naturals. type family (a :: Natural) * (b :: Natural) :: Natural infixl 7 * -- | Exponentiation of type-level naturals. type family (a :: Natural) ^ (b :: Natural) :: Natural infixr 8 ^ -- | Subtraction of type-level naturals. type family (a :: Natural) - (b :: Natural) :: Natural infixl 6 - -- | Division (round down) of natural numbers. Div x 0 is -- undefined (i.e., it cannot be reduced). type family Div (a :: Natural) (b :: Natural) :: Natural infixl 7 `Div` -- | Modulus of natural numbers. Mod x 0 is undefined (i.e., it -- cannot be reduced). type family Mod (a :: Natural) (b :: Natural) :: Natural infixl 7 `Mod` -- | Log base 2 (round down) of natural numbers. Log 0 is -- undefined (i.e., it cannot be reduced). type family Log2 (a :: Natural) :: Natural -- | Concatenation of type-level symbols. type family AppendSymbol (a :: Symbol) (b :: Symbol) :: Symbol -- | Comparison of type-level naturals, as a function. type family CmpNat (a :: Natural) (b :: Natural) :: Ordering -- | Comparison of type-level symbols, as a function. type family CmpSymbol (a :: Symbol) (b :: Symbol) :: Ordering -- | Comparison of type-level characters. type family CmpChar (a :: Char) (b :: Char) :: Ordering -- | Extending a type-level symbol with a type-level character type family ConsSymbol (a :: Char) (b :: Symbol) :: Symbol -- | This type family yields type-level Just storing the first -- character of a symbol and its tail if it is defined and Nothing -- otherwise. type family UnconsSymbol (a :: Symbol) :: Maybe (Char, Symbol) -- | Convert a character to its Unicode code point (cf. ord) type family CharToNat (a :: Char) :: Natural -- | Convert a Unicode code point to a character (cf. chr) type family NatToChar (a :: Natural) :: Char -- | 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.")
--   
type family TypeError (a :: ErrorMessage) :: b -- | 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 infixl 6 :<>: infixl 5 :$$: instance GHC.Classes.Eq (GHC.TypeLits.SChar c) instance GHC.Classes.Eq (GHC.TypeLits.SSymbol s) instance GHC.Classes.Eq GHC.TypeLits.SomeChar instance GHC.Classes.Eq GHC.TypeLits.SomeSymbol instance GHC.Classes.Ord (GHC.TypeLits.SChar c) instance GHC.Classes.Ord (GHC.TypeLits.SSymbol s) instance GHC.Classes.Ord GHC.TypeLits.SomeChar instance GHC.Classes.Ord GHC.TypeLits.SomeSymbol instance GHC.Read.Read GHC.TypeLits.SomeChar instance GHC.Read.Read GHC.TypeLits.SomeSymbol instance GHC.Show.Show (GHC.TypeLits.SChar c) instance GHC.Show.Show (GHC.TypeLits.SSymbol s) instance GHC.Show.Show GHC.TypeLits.SomeChar instance GHC.Show.Show GHC.TypeLits.SomeSymbol instance Data.Type.Coercion.TestCoercion GHC.TypeLits.SChar instance Data.Type.Coercion.TestCoercion GHC.TypeLits.SSymbol instance Data.Type.Equality.TestEquality GHC.TypeLits.SChar instance Data.Type.Equality.TestEquality GHC.TypeLits.SSymbol -- | 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 (p :: k) -- | 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 -> Type) (p :: k) Rec1 :: f p -> Rec1 (f :: k -> Type) (p :: k) [unRec1] :: Rec1 (f :: k -> Type) (p :: k) -> f p -- | Constants, additional parameters and recursion of kind * newtype K1 i c (p :: k) K1 :: c -> K1 i c (p :: k) [unK1] :: K1 i c (p :: k) -> c -- | Meta-information (constructor names, etc.) newtype M1 i (c :: Meta) (f :: k -> Type) (p :: k) M1 :: f p -> M1 i (c :: Meta) (f :: k -> Type) (p :: k) [unM1] :: M1 i (c :: Meta) (f :: k -> Type) (p :: k) -> f p -- | Sums: encode choice between constructors data ( (f :: k -> Type) :+: (g :: k -> Type) ) (p :: k) L1 :: f p -> (:+:) (f :: k -> Type) (g :: k -> Type) (p :: k) R1 :: g p -> (:+:) (f :: k -> Type) (g :: k -> Type) (p :: k) infixr 5 :+: -- | Products: encode multiple arguments to constructors data ( (f :: k -> Type) :*: (g :: k -> Type) ) (p :: k) (:*:) :: f p -> g p -> (:*:) (f :: k -> Type) (g :: k -> Type) (p :: k) infixr 6 :*: infixr 6 :*: -- | Composition of functors newtype ( (f :: k2 -> Type) :.: (g :: k1 -> k2) ) (p :: k1) Comp1 :: f (g p) -> (:.:) (f :: k2 -> Type) (g :: k1 -> k2) (p :: k1) [unComp1] :: (:.:) (f :: k2 -> Type) (g :: k1 -> k2) (p :: k1) -> f (g p) infixr 7 :.: -- | Constants of unlifted kinds data family URec a (p :: k) -- | Type synonym for URec Addr# type UAddr = URec Ptr () :: k -> Type -- | Type synonym for URec Char# type UChar = URec Char :: k -> Type -- | Type synonym for URec Double# type UDouble = URec Double :: k -> Type -- | Type synonym for URec Float# type UFloat = URec Float :: k -> Type -- | Type synonym for URec Int# type UInt = URec Int :: k -> Type -- | Type synonym for URec Word# type UWord = URec Word :: k -> Type -- | Type synonym for encoding recursion (of kind Type) type Rec0 = K1 R :: Type -> k -> Type -- | Tag for K1: recursion (of kind Type) data R -- | Type synonym for encoding meta-information for datatypes type D1 = M1 D :: Meta -> k -> Type -> k -> Type -- | Type synonym for encoding meta-information for constructors type C1 = M1 C :: Meta -> k -> Type -> k -> Type -- | Type synonym for encoding meta-information for record selectors type S1 = M1 S :: Meta -> k -> Type -> k -> Type -- | 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 :: k) -- | The name of the datatype (unqualified) datatypeName :: forall k1 t (f :: k1 -> Type) (a :: k1). Datatype d => t d f a -> [Char] -- | The fully-qualified name of the module where the type is declared moduleName :: forall k1 t (f :: k1 -> Type) (a :: k1). Datatype d => t d f a -> [Char] -- | The package name of the module where the type is declared packageName :: forall k1 t (f :: k1 -> Type) (a :: k1). Datatype d => t d f a -> [Char] -- | Marks if the datatype is actually a newtype isNewtype :: forall k1 t (f :: k1 -> Type) (a :: k1). Datatype d => t d f a -> Bool -- | Class for datatypes that represent data constructors class Constructor (c :: k) -- | The name of the constructor conName :: forall k1 t (f :: k1 -> Type) (a :: k1). Constructor c => t c f a -> [Char] -- | The fixity of the constructor conFixity :: forall k1 t (f :: k1 -> Type) (a :: k1). Constructor c => t c f a -> Fixity -- | Marks if this constructor is a record conIsRecord :: forall k1 t (f :: k1 -> Type) (a :: k1). Constructor c => t c f a -> Bool -- | Class for datatypes that represent records class Selector (s :: k) -- | The name of the selector selName :: forall k1 t (f :: k1 -> Type) (a :: k1). Selector s => t s f a -> [Char] -- | The selector's unpackedness annotation (if any) selSourceUnpackedness :: forall k1 t (f :: k1 -> Type) (a :: k1). Selector s => t s f a -> SourceUnpackedness -- | The selector's strictness annotation (if any) selSourceStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). Selector s => t s f a -> SourceStrictness -- | The strictness that the compiler inferred for the selector selDecidedStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). Selector s => t s f a -> 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. -- -- A Generic instance must satisfy the following laws: -- --
--   from . toid
--   to . fromid
--   
class Generic a where { -- | Generic representation type type Rep a :: Type -> Type; } -- | 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. -- -- A Generic1 instance must satisfy the following laws: -- --
--   from1 . to1id
--   to1 . from1id
--   
class Generic1 (f :: k -> Type) where { -- | Generic representation type type Rep1 (f :: k -> Type) :: k -> Type; } -- | Convert from the datatype to its representation from1 :: forall (a :: k). Generic1 f => f a -> Rep1 f a -- | Convert from the representation to the datatype to1 :: forall (a :: k). Generic1 f => Rep1 f a -> f a -- | A datatype whose instances are defined generically, using the -- Generic representation. Generically1 is a higher-kinded -- version of Generically that uses Generic1. -- -- Generic instances can be derived via Generically A -- using -XDerivingVia. -- --
--   {-# LANGUAGE DeriveGeneric      #-}
--   {-# LANGUAGE DerivingStrategies #-}
--   {-# LANGUAGE DerivingVia        #-}
--   
--   import GHC.Generics (Generic)
--   
--   data V4 a = V4 a a a a
--     deriving stock Generic
--   
--     deriving (Semigroup, Monoid)
--     via Generically (V4 a)
--   
-- -- This corresponds to Semigroup and Monoid instances -- defined by pointwise lifting: -- --
--   instance Semigroup a => Semigroup (V4 a) where
--     (<>) :: V4 a -> V4 a -> V4 a
--     V4 a1 b1 c1 d1 <> V4 a2 b2 c2 d2 =
--       V4 (a1 <> a2) (b1 <> b2) (c1 <> c2) (d1 <> d2)
--   
--   instance Monoid a => Monoid (V4 a) where
--     mempty :: V4 a
--     mempty = V4 mempty mempty mempty mempty
--   
-- -- Historically this required modifying the type class to include generic -- method definitions (-XDefaultSignatures) and deriving it with -- the anyclass strategy (-XDeriveAnyClass). Having a -- /via type/ like Generically decouples the instance from the -- type class. newtype Generically a Generically :: a -> Generically a -- | A type whose instances are defined generically, using the -- Generic1 representation. Generically1 is a higher-kinded -- version of Generically that uses Generic. -- -- Generic instances can be derived for type constructors via -- Generically1 F using -XDerivingVia. -- --
--   {-# LANGUAGE DeriveGeneric      #-}
--   {-# LANGUAGE DerivingStrategies #-}
--   {-# LANGUAGE DerivingVia        #-}
--   
--   import GHC.Generics (Generic)
--   
--   data V4 a = V4 a a a a
--     deriving stock (Functor, Generic1)
--   
--     deriving Applicative
--     via Generically1 V4
--   
-- -- This corresponds to Applicative instances defined by pointwise -- lifting: -- --
--   instance Applicative V4 where
--     pure :: a -> V4 a
--     pure a = V4 a a a a
--   
--     liftA2 :: (a -> b -> c) -> (V4 a -> V4 b -> V4 c)
--     liftA2 (·) (V4 a1 b1 c1 d1) (V4 a2 b2 c2 d2) =
--       V4 (a1 · a2) (b1 · b2) (c1 · c2) (d1 · d2)
--   
-- -- Historically this required modifying the type class to include generic -- method definitions (-XDefaultSignatures) and deriving it with -- the anyclass strategy (-XDeriveAnyClass). Having a -- /via type/ like Generically1 decouples the instance from the -- type class. newtype Generically1 (f :: k -> Type) (a :: k) [Generically1] :: forall {k} (f :: k -> Type) (a :: k). f a -> Generically1 f a instance (GHC.Base.Alternative f, GHC.Base.Alternative g) => GHC.Base.Alternative (f GHC.Generics.:*: g) instance (GHC.Base.Alternative f, GHC.Base.Applicative g) => GHC.Base.Alternative (f GHC.Generics.:.: g) instance (GHC.Generics.Generic1 f, GHC.Base.Alternative (GHC.Generics.Rep1 f)) => GHC.Base.Alternative (GHC.Generics.Generically1 f) instance GHC.Base.Alternative f => GHC.Base.Alternative (GHC.Generics.M1 i c f) instance GHC.Base.Alternative f => GHC.Base.Alternative (GHC.Generics.Rec1 f) instance GHC.Base.Alternative GHC.Generics.U1 instance (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (f GHC.Generics.:*: g) instance (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (f GHC.Generics.:.: g) instance (GHC.Generics.Generic1 f, GHC.Base.Applicative (GHC.Generics.Rep1 f)) => GHC.Base.Applicative (GHC.Generics.Generically1 f) instance GHC.Base.Monoid c => GHC.Base.Applicative (GHC.Generics.K1 i c) instance GHC.Base.Applicative f => GHC.Base.Applicative (GHC.Generics.M1 i c f) instance GHC.Base.Applicative GHC.Generics.Par1 instance GHC.Base.Applicative f => GHC.Base.Applicative (GHC.Generics.Rec1 f) instance GHC.Base.Applicative GHC.Generics.U1 instance GHC.Enum.Bounded GHC.Generics.Associativity instance GHC.Enum.Bounded GHC.Generics.DecidedStrictness instance GHC.Enum.Bounded GHC.Generics.SourceStrictness instance GHC.Enum.Bounded GHC.Generics.SourceUnpackedness instance (GHC.TypeLits.KnownSymbol n, GHC.Generics.SingI f, GHC.Generics.SingI r) => GHC.Generics.Constructor ('GHC.Generics.MetaCons n f r) 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.Enum.Enum GHC.Generics.Associativity instance GHC.Enum.Enum GHC.Generics.DecidedStrictness instance GHC.Enum.Enum GHC.Generics.SourceStrictness instance GHC.Enum.Enum GHC.Generics.SourceUnpackedness instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Classes.Eq (f p), GHC.Classes.Eq (g p)) => GHC.Classes.Eq ((GHC.Generics.:*:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Classes.Eq (f p), GHC.Classes.Eq (g p)) => GHC.Classes.Eq ((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.Classes.Eq GHC.Generics.Associativity instance GHC.Classes.Eq GHC.Generics.DecidedStrictness instance GHC.Classes.Eq GHC.Generics.Fixity instance forall k (f :: k -> *) (a :: k). (GHC.Generics.Generic1 f, GHC.Classes.Eq (GHC.Generics.Rep1 f a)) => GHC.Classes.Eq (GHC.Generics.Generically1 f a) instance forall i c k (p :: k). GHC.Classes.Eq c => GHC.Classes.Eq (GHC.Generics.K1 i c 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.Classes.Eq p => GHC.Classes.Eq (GHC.Generics.Par1 p) instance forall k (f :: k -> *) (p :: k). GHC.Classes.Eq (f p) => GHC.Classes.Eq (GHC.Generics.Rec1 f p) instance GHC.Classes.Eq GHC.Generics.SourceStrictness instance GHC.Classes.Eq GHC.Generics.SourceUnpackedness instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec (GHC.Ptr.Ptr ()) p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Char p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Double p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Float p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Int 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 (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (f GHC.Generics.:*: g) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (f GHC.Generics.:+: g) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (f GHC.Generics.:.: g) instance (GHC.Generics.Generic1 f, GHC.Base.Functor (GHC.Generics.Rep1 f)) => GHC.Base.Functor (GHC.Generics.Generically1 f) instance GHC.Base.Functor (GHC.Generics.K1 i c) instance GHC.Base.Functor f => GHC.Base.Functor (GHC.Generics.M1 i c f) instance GHC.Base.Functor GHC.Generics.Par1 instance GHC.Base.Functor f => GHC.Base.Functor (GHC.Generics.Rec1 f) instance GHC.Base.Functor GHC.Generics.U1 instance GHC.Base.Functor (GHC.Generics.URec (GHC.Ptr.Ptr ())) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Char) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Double) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Float) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Int) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Word) instance GHC.Base.Functor GHC.Generics.V1 instance GHC.Generics.Generic1 Data.Ord.Down instance GHC.Generics.Generic1 (Data.Either.Either a) instance GHC.Generics.Generic1 [] instance GHC.Generics.Generic1 GHC.Maybe.Maybe instance GHC.Generics.Generic1 GHC.Base.NonEmpty instance GHC.Generics.Generic1 GHC.Generics.Par1 instance GHC.Generics.Generic1 GHC.Tuple.Prim.Solo instance GHC.Generics.Generic1 ((,,,,,,,,,) a b c d e f g h i) instance GHC.Generics.Generic1 ((,,,,,,,,,,) a b c d e f g h i j) instance GHC.Generics.Generic1 ((,,,,,,,,,,,) a b c d e f g h i j k) instance GHC.Generics.Generic1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) instance GHC.Generics.Generic1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) instance GHC.Generics.Generic1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) 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.Generics.Generic1 ((,,,,,,,) a b c d e f g) instance GHC.Generics.Generic1 ((,,,,,,,,) a b c d e f g h) instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (f GHC.Generics.:*: g) instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (f GHC.Generics.:+: g) instance forall (f :: * -> *) k (g :: k -> *). GHC.Base.Functor f => GHC.Generics.Generic1 (f GHC.Generics.:.: g) instance GHC.Generics.Generic1 (GHC.Generics.K1 i c) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *). GHC.Generics.Generic1 (GHC.Generics.M1 i c f) instance GHC.Generics.Generic1 Data.Proxy.Proxy instance forall k (f :: k -> *). GHC.Generics.Generic1 (GHC.Generics.Rec1 f) instance GHC.Generics.Generic1 GHC.Generics.U1 instance GHC.Generics.Generic1 (GHC.Generics.URec (GHC.Ptr.Ptr ())) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Char) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Double) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Float) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Int) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Word) instance GHC.Generics.Generic1 GHC.Generics.V1 instance forall k (f :: k -> *) (g :: k -> *) (p :: k). GHC.Generics.Generic ((GHC.Generics.:*:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). GHC.Generics.Generic ((GHC.Generics.:+:) f g p) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Generics.Generic ((GHC.Generics.:.:) f g p) instance GHC.Generics.Generic GHC.Generics.Associativity instance GHC.Generics.Generic GHC.Types.Bool instance GHC.Generics.Generic GHC.Generics.DecidedStrictness instance GHC.Generics.Generic (Data.Ord.Down a) instance GHC.Generics.Generic (Data.Either.Either a b) instance GHC.Generics.Generic GHC.Fingerprint.Type.Fingerprint instance GHC.Generics.Generic GHC.Generics.Fixity instance GHC.Generics.Generic GHC.Unicode.GeneralCategory instance forall i c k (p :: k). GHC.Generics.Generic (GHC.Generics.K1 i c p) instance GHC.Generics.Generic [a] instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Generics.Generic (GHC.Generics.M1 i c f p) instance GHC.Generics.Generic (GHC.Maybe.Maybe a) instance GHC.Generics.Generic (GHC.Base.NonEmpty a) instance GHC.Generics.Generic GHC.Types.Ordering instance GHC.Generics.Generic (GHC.Generics.Par1 p) instance forall k (t :: k). GHC.Generics.Generic (Data.Proxy.Proxy t) instance forall k (f :: k -> *) (p :: k). GHC.Generics.Generic (GHC.Generics.Rec1 f p) instance GHC.Generics.Generic (GHC.Tuple.Prim.Solo a) instance GHC.Generics.Generic GHC.Generics.SourceStrictness instance GHC.Generics.Generic GHC.Generics.SourceUnpackedness instance GHC.Generics.Generic GHC.Stack.Types.SrcLoc instance GHC.Generics.Generic (a, b, c, d, e, f, g, h, i, j) instance GHC.Generics.Generic (a, b, c, d, e, f, g, h, i, j, k) instance GHC.Generics.Generic (a, b, c, d, e, f, g, h, i, j, k, l) instance GHC.Generics.Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) instance GHC.Generics.Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) instance GHC.Generics.Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 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.Generic (a, b, c, d, e, f, g, h) instance GHC.Generics.Generic (a, b, c, d, e, f, g, h, i) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec (GHC.Ptr.Ptr ()) p) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Char p) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Double p) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Float p) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Int p) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Word p) instance GHC.Generics.Generic () instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.V1 p) instance GHC.Generics.Generic GHC.Base.Void instance GHC.Ix.Ix GHC.Generics.Associativity instance GHC.Ix.Ix GHC.Generics.DecidedStrictness instance GHC.Ix.Ix GHC.Generics.SourceStrictness instance GHC.Ix.Ix GHC.Generics.SourceUnpackedness instance (GHC.Base.MonadPlus f, GHC.Base.MonadPlus g) => GHC.Base.MonadPlus (f GHC.Generics.:*: g) instance GHC.Base.MonadPlus f => GHC.Base.MonadPlus (GHC.Generics.M1 i c f) instance GHC.Base.MonadPlus f => GHC.Base.MonadPlus (GHC.Generics.Rec1 f) instance GHC.Base.MonadPlus GHC.Generics.U1 instance (GHC.Base.Monad f, GHC.Base.Monad g) => GHC.Base.Monad (f GHC.Generics.:*: g) instance GHC.Base.Monad f => GHC.Base.Monad (GHC.Generics.M1 i c f) instance GHC.Base.Monad GHC.Generics.Par1 instance GHC.Base.Monad f => GHC.Base.Monad (GHC.Generics.Rec1 f) instance GHC.Base.Monad GHC.Generics.U1 instance forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Base.Monoid (f p), GHC.Base.Monoid (g p)) => GHC.Base.Monoid ((GHC.Generics.:*:) f g p) instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Base.Monoid (f (g p)) => GHC.Base.Monoid ((GHC.Generics.:.:) f g p) instance (GHC.Generics.Generic a, GHC.Base.Monoid (GHC.Generics.Rep a ())) => GHC.Base.Monoid (GHC.Generics.Generically a) instance forall k c i (p :: k). GHC.Base.Monoid c => GHC.Base.Monoid (GHC.Generics.K1 i c p) instance forall k (f :: k -> *) (p :: k) i (c :: GHC.Generics.Meta). GHC.Base.Monoid (f p) => GHC.Base.Monoid (GHC.Generics.M1 i c f p) instance GHC.Base.Monoid p => GHC.Base.Monoid (GHC.Generics.Par1 p) instance forall k (f :: k -> *) (p :: k). GHC.Base.Monoid (f p) => GHC.Base.Monoid (GHC.Generics.Rec1 f p) instance forall k (p :: k). GHC.Base.Monoid (GHC.Generics.U1 p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Classes.Ord (f p), GHC.Classes.Ord (g p)) => GHC.Classes.Ord ((GHC.Generics.:*:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Classes.Ord (f p), GHC.Classes.Ord (g p)) => GHC.Classes.Ord ((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 GHC.Classes.Ord GHC.Generics.Associativity instance GHC.Classes.Ord GHC.Generics.DecidedStrictness instance GHC.Classes.Ord GHC.Generics.Fixity instance forall k (f :: k -> *) (a :: k). (GHC.Generics.Generic1 f, GHC.Classes.Ord (GHC.Generics.Rep1 f a)) => GHC.Classes.Ord (GHC.Generics.Generically1 f a) instance forall i c k (p :: k). GHC.Classes.Ord c => GHC.Classes.Ord (GHC.Generics.K1 i c 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 GHC.Classes.Ord p => GHC.Classes.Ord (GHC.Generics.Par1 p) instance forall k (f :: k -> *) (p :: k). GHC.Classes.Ord (f p) => GHC.Classes.Ord (GHC.Generics.Rec1 f p) instance GHC.Classes.Ord GHC.Generics.SourceStrictness instance GHC.Classes.Ord GHC.Generics.SourceUnpackedness instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec (GHC.Ptr.Ptr ()) p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Char p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Double p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Float p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Int p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Word p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.V1 p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Read.Read (f p), GHC.Read.Read (g p)) => GHC.Read.Read ((GHC.Generics.:*:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Read.Read (f p), GHC.Read.Read (g p)) => GHC.Read.Read ((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 GHC.Read.Read GHC.Generics.Associativity instance GHC.Read.Read GHC.Generics.DecidedStrictness instance GHC.Read.Read GHC.Generics.Fixity instance forall i c k (p :: k). GHC.Read.Read c => GHC.Read.Read (GHC.Generics.K1 i c 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 GHC.Read.Read p => GHC.Read.Read (GHC.Generics.Par1 p) instance forall k (f :: k -> *) (p :: k). GHC.Read.Read (f p) => GHC.Read.Read (GHC.Generics.Rec1 f p) instance GHC.Read.Read GHC.Generics.SourceStrictness instance GHC.Read.Read GHC.Generics.SourceUnpackedness instance forall k (p :: k). GHC.Read.Read (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Read.Read (GHC.Generics.V1 p) 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 forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Base.Semigroup (f p), GHC.Base.Semigroup (g p)) => GHC.Base.Semigroup ((GHC.Generics.:*:) f g p) instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Base.Semigroup (f (g p)) => GHC.Base.Semigroup ((GHC.Generics.:.:) f g p) instance (GHC.Generics.Generic a, GHC.Base.Semigroup (GHC.Generics.Rep a ())) => GHC.Base.Semigroup (GHC.Generics.Generically a) instance forall k c i (p :: k). GHC.Base.Semigroup c => GHC.Base.Semigroup (GHC.Generics.K1 i c p) instance forall k (f :: k -> *) (p :: k) i (c :: GHC.Generics.Meta). GHC.Base.Semigroup (f p) => GHC.Base.Semigroup (GHC.Generics.M1 i c f p) instance GHC.Base.Semigroup p => GHC.Base.Semigroup (GHC.Generics.Par1 p) instance forall k (f :: k -> *) (p :: k). GHC.Base.Semigroup (f p) => GHC.Base.Semigroup (GHC.Generics.Rec1 f p) instance forall k (p :: k). GHC.Base.Semigroup (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Base.Semigroup (GHC.Generics.V1 p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Show.Show (f p), GHC.Show.Show (g p)) => GHC.Show.Show ((GHC.Generics.:*:) f g p) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). (GHC.Show.Show (f p), GHC.Show.Show (g p)) => GHC.Show.Show ((GHC.Generics.:+:) f g p) 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 GHC.Show.Show GHC.Generics.Associativity instance GHC.Show.Show GHC.Generics.DecidedStrictness instance GHC.Show.Show GHC.Generics.Fixity instance forall i c k (p :: k). GHC.Show.Show c => GHC.Show.Show (GHC.Generics.K1 i c p) 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 GHC.Show.Show p => GHC.Show.Show (GHC.Generics.Par1 p) instance forall k (f :: k -> *) (p :: k). GHC.Show.Show (f p) => GHC.Show.Show (GHC.Generics.Rec1 f p) instance GHC.Show.Show GHC.Generics.SourceStrictness instance GHC.Show.Show GHC.Generics.SourceUnpackedness instance forall k (p :: k). GHC.Show.Show (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Char p) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Double p) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Float p) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Int p) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Word p) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.V1 p) instance GHC.Generics.SingI 'GHC.Generics.LeftAssociative instance GHC.Generics.SingI 'GHC.Generics.NotAssociative instance GHC.Generics.SingI 'GHC.Generics.RightAssociative instance GHC.Generics.SingI 'GHC.Types.False instance GHC.Generics.SingI 'GHC.Types.True instance GHC.Generics.SingI 'GHC.Generics.DecidedLazy instance GHC.Generics.SingI 'GHC.Generics.DecidedStrict instance GHC.Generics.SingI 'GHC.Generics.DecidedUnpack instance (GHC.Generics.SingI a, GHC.TypeNats.KnownNat n) => GHC.Generics.SingI ('GHC.Generics.InfixI a n) instance GHC.Generics.SingI 'GHC.Generics.PrefixI instance forall a1 (a2 :: a1). GHC.Generics.SingI a2 => GHC.Generics.SingI ('GHC.Maybe.Just a2) instance GHC.Generics.SingI 'GHC.Maybe.Nothing 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.NoSourceUnpackedness instance GHC.Generics.SingI 'GHC.Generics.SourceNoUnpack instance GHC.Generics.SingI 'GHC.Generics.SourceUnpack instance GHC.TypeLits.KnownSymbol a => GHC.Generics.SingI a instance GHC.Generics.SingKind GHC.Generics.Associativity instance GHC.Generics.SingKind GHC.Types.Bool instance GHC.Generics.SingKind GHC.Generics.DecidedStrictness instance GHC.Generics.SingKind GHC.Generics.FixityI instance GHC.Generics.SingKind a => GHC.Generics.SingKind (GHC.Maybe.Maybe a) instance GHC.Generics.SingKind GHC.Generics.SourceStrictness instance GHC.Generics.SingKind GHC.Generics.SourceUnpackedness instance GHC.Generics.SingKind GHC.Types.Symbol -- | A type a is a Monoid if it provides an associative -- function (<>) that lets you combine any two values of -- type a into one, and a neutral element (mempty) such -- that -- --
--   a <> mempty == mempty <> a == a
--   
-- -- A Monoid is a Semigroup with the added requirement of a -- neutral element. Thus any Monoid is a Semigroup, but not -- the other way around. -- --

Examples

-- -- The Sum monoid is defined by the numerical addition operator -- and `0` as neutral element: -- --
--   >>> mempty :: Sum Int
--   Sum {getSum = 0}
--   
--   >>> Sum 1 <> Sum 2 <> Sum 3 <> Sum 4 :: Sum Int
--   Sum {getSum = 10}
--   
-- -- We can combine multiple values in a list into a single value using the -- mconcat function. Note that we have to specify the type here -- since Int is a monoid under several different operations: -- --
--   >>> mconcat [1,2,3,4] :: Sum Int
--   Sum {getSum = 10}
--   
--   >>> mconcat [] :: Sum Int
--   Sum {getSum = 0}
--   
-- -- Another valid monoid instance of Int is Product It is -- defined by multiplication and `1` as neutral element: -- --
--   >>> Product 1 <> Product 2 <> Product 3 <> Product 4 :: Product Int
--   Product {getProduct = 24}
--   
--   >>> mconcat [1,2,3,4] :: Product Int
--   Product {getProduct = 24}
--   
--   >>> mconcat [] :: Product Int
--   Product {getProduct = 1}
--   
module Data.Monoid -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following: -- -- -- -- You can alternatively define mconcat instead of mempty, -- in which case the laws are: -- -- -- -- 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. -- -- NOTE: Semigroup is a superclass of Monoid since -- base-4.11.0.0. class Semigroup a => Monoid a -- | Identity of mappend -- --

Examples

-- --
--   >>> "Hello world" <> mempty
--   "Hello world"
--   
-- --
--   >>> mempty <> [1, 2, 3]
--   [1,2,3]
--   
mempty :: Monoid a => a -- | An associative operation -- -- NOTE: This method is redundant and has the default -- implementation mappend = (<>) since -- base-4.11.0.0. Should it be implemented manually, since -- mappend is a synonym for (<>), it is expected that -- the two functions are defined the same way. In a future GHC release -- mappend will be removed from Monoid. 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 ["Hello", " ", "Haskell", "!"]
--   "Hello Haskell!"
--   
mconcat :: Monoid a => [a] -> a -- | An associative operation. -- --

Examples

-- --
--   >>> [1,2,3] <> [4,5,6]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> Just [1, 2, 3] <> Just [4, 5, 6]
--   Just [1,2,3,4,5,6]
--   
-- --
--   >>> putStr "Hello, " <> putStrLn "World!"
--   Hello, World!
--   
(<>) :: Semigroup a => a -> a -> a infixr 6 <> -- | The dual of a Monoid, obtained by swapping the arguments of -- (<>). -- --
--   Dual a <> Dual b == Dual (b <> a)
--   
-- --

Examples

-- --
--   >>> Dual "Hello" <> Dual "World"
--   Dual {getDual = "WorldHello"}
--   
-- --
--   >>> Dual (Dual "Hello") <> Dual (Dual "World")
--   Dual {getDual = Dual {getDual = "HelloWorld"}}
--   
newtype Dual a Dual :: a -> Dual a [getDual] :: Dual a -> a -- | The monoid of endomorphisms under composition. -- --
--   Endo f <> Endo g == Endo (f . g)
--   
-- --

Examples

-- --
--   >>> let computation = Endo ("Hello, " ++) <> Endo (++ "!")
--   
--   >>> appEndo computation "Haskell"
--   "Hello, Haskell!"
--   
-- --
--   >>> let computation = Endo (*3) <> Endo (+1)
--   
--   >>> appEndo computation 1
--   6
--   
newtype Endo a Endo :: (a -> a) -> Endo a [appEndo] :: Endo a -> a -> a -- | Boolean monoid under conjunction (&&). -- --
--   All x <> All y = All (x && y)
--   
-- --

Examples

-- --
--   >>> All True <> mempty <> All False)
--   All {getAll = False}
--   
-- --
--   >>> mconcat (map (\x -> All (even x)) [2,4,6,7,8])
--   All {getAll = False}
--   
-- --
--   >>> All True <> mempty
--   All {getAll = True}
--   
newtype All All :: Bool -> All [getAll] :: All -> Bool -- | Boolean monoid under disjunction (||). -- --
--   Any x <> Any y = Any (x || y)
--   
-- --

Examples

-- --
--   >>> Any True <> mempty <> Any False
--   Any {getAny = True}
--   
-- --
--   >>> mconcat (map (\x -> Any (even x)) [2,4,6,7,8])
--   Any {getAny = True}
--   
-- --
--   >>> Any False <> mempty
--   Any {getAny = False}
--   
newtype Any Any :: Bool -> Any [getAny] :: Any -> Bool -- | Monoid under addition. -- --
--   Sum a <> Sum b = Sum (a + b)
--   
-- --

Examples

-- --
--   >>> Sum 1 <> Sum 2 <> mempty
--   Sum {getSum = 3}
--   
-- --
--   >>> mconcat [ Sum n | n <- [3 .. 9]]
--   Sum {getSum = 42}
--   
newtype Sum a Sum :: a -> Sum a [getSum] :: Sum a -> a -- | Monoid under multiplication. -- --
--   Product x <> Product y == Product (x * y)
--   
-- --

Examples

-- --
--   >>> Product 3 <> Product 4 <> mempty
--   Product {getProduct = 12}
--   
-- --
--   >>> mconcat [ Product n | n <- [2 .. 10]]
--   Product {getProduct = 3628800}
--   
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. -- -- Beware that Data.Monoid.First is different from -- Data.Semigroup.First. The former returns the first -- non-Nothing, so Data.Monoid.First Nothing <> x = -- x. The latter simply returns the first value, thus -- Data.Semigroup.First Nothing <> x = Data.Semigroup.First -- Nothing. -- --

Examples

-- --
--   >>> First (Just "hello") <> First Nothing <> First (Just "world")
--   First {getFirst = Just "hello"}
--   
-- --
--   >>> First Nothing <> mempty
--   First {getFirst = Nothing}
--   
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) -- -- Data.Semigroup.Last. The former returns the last -- non-Nothing, so x <> Data.Monoid.Last Nothing = -- x. The latter simply returns the last value, thus x <> -- Data.Semigroup.Last Nothing = Data.Semigroup.Last Nothing. -- --

Examples

-- --
--   >>> Last (Just "hello") <> Last Nothing <> Last (Just "world")
--   Last {getLast = Just "world"}
--   
-- --
--   >>> Last Nothing <> mempty
--   Last {getLast = Nothing}
--   
newtype Last a Last :: Maybe a -> Last a [getLast] :: Last a -> Maybe a -- | Monoid under <|>. -- --
--   Alt l <> Alt r == Alt (l <|> r)
--   
-- --

Examples

-- --
--   >>> Alt (Just 12) <> Alt (Just 24)
--   Alt {getAlt = Just 12}
--   
-- --
--   >>> Alt Nothing <> Alt (Just 24)
--   Alt {getAlt = Just 24}
--   
newtype Alt (f :: k -> Type) (a :: k) Alt :: f a -> Alt (f :: k -> Type) (a :: k) [getAlt] :: Alt (f :: k -> Type) (a :: k) -> f a -- | This data type witnesses the lifting of a Monoid into an -- Applicative pointwise. -- --

Examples

-- --
--   >>> Ap (Just [1, 2, 3]) <> Ap Nothing
--   Ap {getAp = Nothing}
--   
-- --
--   >>> Ap [Sum 10, Sum 20] <> Ap [Sum 1, Sum 2]
--   Ap {getAp = [Sum {getSum = 11},Sum {getSum = 12},Sum {getSum = 21},Sum {getSum = 22}]}
--   
newtype Ap (f :: k -> Type) (a :: k) Ap :: f a -> Ap (f :: k -> Type) (a :: k) [getAp] :: Ap (f :: k -> Type) (a :: k) -> f a instance GHC.Base.Alternative f => GHC.Base.Alternative (Data.Monoid.Ap f) instance GHC.Base.Applicative f => GHC.Base.Applicative (Data.Monoid.Ap f) instance GHC.Base.Applicative Data.Monoid.First instance GHC.Base.Applicative Data.Monoid.Last instance (GHC.Base.Applicative f, GHC.Enum.Bounded a) => GHC.Enum.Bounded (Data.Monoid.Ap f a) instance forall k (f :: k -> *) (a :: k). GHC.Enum.Enum (f a) => GHC.Enum.Enum (Data.Monoid.Ap f a) instance forall k (f :: k -> *) (a :: k). GHC.Classes.Eq (f a) => GHC.Classes.Eq (Data.Monoid.Ap f a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Monoid.First a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Monoid.Last a) instance GHC.Base.Functor f => GHC.Base.Functor (Data.Monoid.Ap f) instance GHC.Base.Functor Data.Monoid.First instance GHC.Base.Functor Data.Monoid.Last instance GHC.Generics.Generic1 Data.Monoid.First instance GHC.Generics.Generic1 Data.Monoid.Last instance forall k (f :: k -> *). GHC.Generics.Generic1 (Data.Monoid.Ap f) instance forall k (f :: k -> *) (a :: k). GHC.Generics.Generic (Data.Monoid.Ap f a) instance GHC.Generics.Generic (Data.Monoid.First a) instance GHC.Generics.Generic (Data.Monoid.Last a) instance Control.Monad.Fail.MonadFail f => Control.Monad.Fail.MonadFail (Data.Monoid.Ap f) instance GHC.Base.Monad f => GHC.Base.Monad (Data.Monoid.Ap f) instance GHC.Base.Monad Data.Monoid.First instance GHC.Base.Monad Data.Monoid.Last instance GHC.Base.MonadPlus f => GHC.Base.MonadPlus (Data.Monoid.Ap f) instance (GHC.Base.Applicative f, GHC.Base.Monoid a) => GHC.Base.Monoid (Data.Monoid.Ap f a) instance GHC.Base.Monoid (Data.Monoid.First a) instance GHC.Base.Monoid (Data.Monoid.Last a) instance (GHC.Base.Applicative f, GHC.Num.Num a) => GHC.Num.Num (Data.Monoid.Ap f a) instance forall k (f :: k -> *) (a :: k). GHC.Classes.Ord (f a) => GHC.Classes.Ord (Data.Monoid.Ap f a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Monoid.First a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Monoid.Last a) instance forall k (f :: k -> *) (a :: k). GHC.Read.Read (f a) => GHC.Read.Read (Data.Monoid.Ap f a) instance GHC.Read.Read a => GHC.Read.Read (Data.Monoid.First a) instance GHC.Read.Read a => GHC.Read.Read (Data.Monoid.Last a) instance (GHC.Base.Applicative f, GHC.Base.Semigroup a) => GHC.Base.Semigroup (Data.Monoid.Ap f a) instance GHC.Base.Semigroup (Data.Monoid.First a) instance GHC.Base.Semigroup (Data.Monoid.Last a) instance forall k (f :: k -> *) (a :: k). GHC.Show.Show (f a) => GHC.Show.Show (Data.Monoid.Ap f a) instance GHC.Show.Show a => GHC.Show.Show (Data.Monoid.First a) instance GHC.Show.Show a => GHC.Show.Show (Data.Monoid.Last a) -- | 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 -- | 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 is non-empty and all elements are -- equal to the first one. -- -- group is a special case of groupBy, which allows the -- programmer to supply their own equality test. -- -- It's often preferable to use Data.List.NonEmpty.group, -- which provides type-level guarantees of non-emptiness of inner lists. -- --

Examples

-- --
--   >>> group "Mississippi"
--   ["M","i","ss","i","ss","i","pp","i"]
--   
-- --
--   >>> group [1, 1, 1, 2, 2, 3, 4, 5, 5]
--   [[1,1,1],[2,2],[3],[4],[5,5]]
--   
group :: Eq a => [a] -> [[a]] -- | repeat x is an infinite list, with x the -- value of every element. -- --

Examples

-- --
--   >>> take 10 $ repeat 17
--   [17,17,17,17,17,17,17,17,17, 17]
--   
-- --
--   >>> repeat undefined
--   [*** Exception: Prelude.undefined
--   
repeat :: a -> [a] -- | <math>. zipWith generalises zip by zipping with -- the function given as the first argument, instead of a tupling -- function. -- --
--   zipWith (,) xs ys == zip xs ys
--   zipWith f [x1,x2,x3..] [y1,y2,y3..] == [f x1 y1, f x2 y2, f x3 y3..]
--   
-- -- zipWith is right-lazy: -- --
--   >>> let f = undefined
--   
--   >>> zipWith f [] undefined
--   []
--   
-- -- zipWith is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. -- --

Examples

-- -- zipWith (+) can be applied to two lists to -- produce the list of corresponding sums: -- --
--   >>> zipWith (+) [1, 2, 3] [4, 5, 6]
--   [5,7,9]
--   
-- --
--   >>> zipWith (++) ["hello ", "foo"] ["world!", "bar"]
--   ["hello world!","foobar"]
--   
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | unzip transforms a list of pairs into a list of first -- components and a list of second components. -- --

Examples

-- --
--   >>> unzip []
--   ([],[])
--   
-- --
--   >>> unzip [(1, 'a'), (2, 'b')]
--   ([1,2],"ab")
--   
unzip :: [(a, b)] -> ([a], [b]) -- | <math>. Extract the first element of a list, which must be -- non-empty. -- --
Examples
-- --
--   >>> head [1, 2, 3]
--   1
--   
-- --
--   >>> head [1..]
--   1
--   
-- --
--   >>> head []
--   *** Exception: Prelude.head: empty list
--   
-- | Warning: This is a partial function, it throws an error on empty -- lists. Use pattern matching or Data.List.uncons instead. Consider -- refactoring to use Data.List.NonEmpty. head :: HasCallStack => [a] -> a -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n >= length -- xs. -- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. -- --

Examples

-- --
--   >>> 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]
--   
drop :: Int -> [a] -> [a] -- | 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. For the result to be -- Nothing, the list must be finite. -- --

Examples

-- --
--   >>> findIndex isSpace "Hello World!"
--   Just 5
--   
-- --
--   >>> findIndex odd [0, 2, 4, 6]
--   Nothing
--   
-- --
--   >>> findIndex even [1..]
--   Just 1
--   
-- --
--   >>> findIndex odd [0, 2 ..]
--   * hangs forever *
--   
findIndex :: (a -> Bool) -> [a] -> Maybe Int -- | Concatenate a list of lists. -- --

Examples

-- --
--   >>> concat [[1,2,3], [4,5], [6], []]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> concat []
--   []
--   
-- --
--   >>> concat [[42]]
--   [42]
--   
concat :: [[a]] -> [a] -- | Map a function returning a list over a list and concatenate the -- results. concatMap can be seen as the composition of -- concat and map. -- --
--   concatMap f xs == (concat . map f) xs
--   
-- --

Examples

-- --
--   >>> concatMap (\i -> [-i,i]) []
--   []
--   
-- --
--   >>> concatMap (\i -> [-i, i]) [1, 2, 3]
--   [-1,1,-2,2,-3,3]
--   
-- --
--   >>> concatMap ('replicate' 3) [0, 2, 4]
--   [0,0,0,2,2,2,4,4,4]
--   
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. -- --

Examples

-- --
--   >>> and []
--   True
--   
-- --
--   >>> and [True]
--   True
--   
-- --
--   >>> and [False]
--   False
--   
-- --
--   >>> and [True, True, False]
--   False
--   
-- --
--   >>> and (False : repeat True) -- Infinite list [False,True,True,True,True,True,True...
--   False
--   
-- --
--   >>> and (repeat True)
--   * Hangs forever *
--   
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. -- --

Examples

-- --
--   >>> or []
--   False
--   
-- --
--   >>> or [True]
--   True
--   
-- --
--   >>> or [False]
--   False
--   
-- --
--   >>> or [True, True, False]
--   True
--   
-- --
--   >>> or (True : repeat False) -- Infinite list [True,False,False,False,False,False,False...
--   True
--   
-- --
--   >>> or (repeat False)
--   * Hangs forever *
--   
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. -- --

Examples

-- --
--   >>> any (> 3) []
--   False
--   
-- --
--   >>> any (> 3) [1,2]
--   False
--   
-- --
--   >>> any (> 3) [1,2,3,4,5]
--   True
--   
-- --
--   >>> any (> 3) [1..]
--   True
--   
-- --
--   >>> any (> 3) [0, -1..]
--   * Hangs forever *
--   
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. -- --

Examples

-- --
--   >>> all (> 3) []
--   True
--   
-- --
--   >>> all (> 3) [1,2]
--   False
--   
-- --
--   >>> all (> 3) [1,2,3,4,5]
--   False
--   
-- --
--   >>> all (> 3) [1..]
--   False
--   
-- --
--   >>> all (> 3) [4..]
--   * Hangs forever *
--   
all :: (a -> Bool) -> [a] -> Bool -- | The maximumBy function is the non-overloaded version of -- maximum, which 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. -- --

Examples

-- -- We can use this to find the longest entry of a list: -- --
--   >>> maximumBy (\x y -> compare (length x) (length y)) ["Hello", "World", "!", "Longest", "bar"]
--   "Longest"
--   
-- --
--   >>> minimumBy (\(a, b) (c, d) -> compare (abs (a - b)) (abs (c - d))) [(10, 15), (1, 2), (3, 5)]
--   (10, 15)
--   
maximumBy :: (a -> a -> Ordering) -> [a] -> a -- | The minimumBy function is the non-overloaded version of -- minimum, which 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. -- --

Examples

-- -- We can use this to find the shortest entry of a list: -- --
--   >>> minimumBy (\x y -> compare (length x) (length y)) ["Hello", "World", "!", "Longest", "bar"]
--   "!"
--   
-- --
--   >>> minimumBy (\(a, b) (c, d) -> compare (abs (a - b)) (abs (c - d))) [(10, 15), (1, 2), (3, 5)]
--   (1, 2)
--   
minimumBy :: (a -> a -> Ordering) -> [a] -> a -- | notElem is the negation of elem. -- --

Examples

-- --
--   >>> 3 `notElem` []
--   True
--   
-- --
--   >>> 3 `notElem` [1,2]
--   True
--   
-- --
--   >>> 3 `notElem` [1,2,3,4,5]
--   False
--   
-- --
--   >>> 3 `notElem` [1..]
--   False
--   
-- --
--   >>> 3 `notElem` [4..]
--   * Hangs forever *
--   
notElem :: Eq a => a -> [a] -> Bool infix 4 `notElem` -- | 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. For the result to be Nothing, the -- list must be finite. -- --

Examples

-- --
--   >>> find (> 4) [1..]
--   Just 5
--   
-- --
--   >>> find (< 0) [1..10]
--   Nothing
--   
-- --
--   >>> find ('a' `elem`) ["john", "marcus", "paul"]
--   Just "marcus"
--   
find :: (a -> Bool) -> [a] -> Maybe 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. Note that -- unlike foldr, the accumulated value must be of the same type as -- the list elements. -- --
--   >>> foldr1 (+) [1..4]
--   10
--   
--   >>> foldr1 (+) []
--   *** Exception: Prelude.foldr1: empty list
--   
--   >>> foldr1 (-) [1..4]
--   -2
--   
--   >>> foldr1 (&&) [True, False, True, True]
--   False
--   
--   >>> foldr1 (||) [False, False, True, True]
--   True
--   
--   >>> force $ foldr1 (+) [1..]
--   *** Exception: stack overflow
--   
foldr1 :: HasCallStack => (a -> a -> a) -> [a] -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty lists. Note that -- unlike foldl, the accumulated value must be of the same type as -- the list elements. -- --
--   >>> foldl1 (+) [1..4]
--   10
--   
--   >>> foldl1 (+) []
--   *** Exception: Prelude.foldl1: empty list
--   
--   >>> foldl1 (-) [1..4]
--   -8
--   
--   >>> foldl1 (&&) [True, False, True, True]
--   False
--   
--   >>> foldl1 (||) [False, False, True, True]
--   True
--   
--   >>> foldl1 (+) [1..]
--   * Hangs forever *
--   
foldl1 :: HasCallStack => (a -> a -> a) -> [a] -> a -- | A strict version of foldl1. foldl1' :: HasCallStack => (a -> a -> a) -> [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 (+) 0 [1..4]
--   10
--   
--   >>> foldl (+) 42 []
--   42
--   
--   >>> foldl (-) 100 [1..4]
--   90
--   
--   >>> foldl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   "dcbafoo"
--   
--   >>> foldl (+) 0 [1..]
--   * Hangs forever *
--   
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 -- | (++) appends 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. -- --

Performance considerations

-- -- This function takes linear time in the number of elements of the -- first list. Thus it is better to associate repeated -- applications of (++) to the right (which is the default -- behaviour): xs ++ (ys ++ zs) or simply xs ++ ys ++ -- zs, but not (xs ++ ys) ++ zs. For the same reason -- concat = foldr (++) [] has -- linear performance, while foldl (++) [] is -- prone to quadratic slowdown -- --

Examples

-- --
--   >>> [1, 2, 3] ++ [4, 5, 6]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> [] ++ [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> [3, 2, 1] ++ []
--   [3,2,1]
--   
(++) :: [a] -> [a] -> [a] infixr 5 ++ -- | <math>. Extract the last element of a list, which must be finite -- and non-empty. -- -- WARNING: This function is partial. Consider using unsnoc -- instead. -- --

Examples

-- --
--   >>> last [1, 2, 3]
--   3
--   
-- --
--   >>> last [1..]
--   * Hangs forever *
--   
-- --
--   >>> last []
--   *** Exception: Prelude.last: empty list
--   
last :: HasCallStack => [a] -> a -- | <math>. Extract the elements after the head of a list, which -- must be non-empty. -- --

Examples

-- --
--   >>> tail [1, 2, 3]
--   [2,3]
--   
-- --
--   >>> tail [1]
--   []
--   
-- --
--   >>> tail []
--   *** Exception: Prelude.tail: empty list
--   
-- | Warning: This is a partial function, it throws an error on empty -- lists. Replace it with drop 1, or use pattern matching or -- Data.List.uncons instead. Consider refactoring to use -- Data.List.NonEmpty. tail :: HasCallStack => [a] -> [a] -- | <math>. Return all the elements of a list except the last one. -- The list must be non-empty. -- -- WARNING: This function is partial. Consider using unsnoc -- instead. -- --

Examples

-- --
--   >>> init [1, 2, 3]
--   [1,2]
--   
-- --
--   >>> init [1]
--   []
--   
-- --
--   >>> init []
--   *** Exception: Prelude.init: empty list
--   
init :: HasCallStack => [a] -> [a] -- | <math>. Decompose a list into its head and tail. -- -- -- --

Examples

-- --
--   >>> uncons []
--   Nothing
--   
-- --
--   >>> uncons [1]
--   Just (1,[])
--   
-- --
--   >>> uncons [1, 2, 3]
--   Just (1,[2,3])
--   
uncons :: [a] -> Maybe (a, [a]) -- | <math>. Decompose a list into init and last. -- -- -- -- unsnoc is dual to uncons: for a finite list xs -- --
--   unsnoc xs = (\(hd, tl) -> (reverse tl, hd)) <$> uncons (reverse xs)
--   
-- --

Examples

-- --
--   >>> unsnoc []
--   Nothing
--   
-- --
--   >>> unsnoc [1]
--   Just ([],1)
--   
-- --
--   >>> unsnoc [1, 2, 3]
--   Just ([1,2],3)
--   
-- --

Laziness

-- --
--   >>> fst <$> unsnoc [undefined]
--   Just []
--   
-- --
--   >>> head . fst <$> unsnoc (1 : undefined)
--   Just *** Exception: Prelude.undefined
--   
-- --
--   >>> head . fst <$> unsnoc (1 : 2 : undefined)
--   Just 1
--   
unsnoc :: [a] -> Maybe ([a], a) -- | Construct a list from a single element. -- --

Examples

-- --
--   >>> singleton True
--   [True]
--   
-- --
--   >>> singleton [1, 2, 3]
--   [[1,2,3]]
--   
-- --
--   >>> singleton 'c'
--   "c"
--   
singleton :: a -> [a] -- | <math>. Test whether a list is empty. -- --
--   >>> null []
--   True
--   
--   >>> null [1]
--   False
--   
--   >>> null [1..]
--   False
--   
null :: [a] -> Bool -- | <math>. 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 []
--   0
--   
--   >>> length ['a', 'b', 'c']
--   3
--   
--   >>> length [1..]
--   * Hangs forever *
--   
length :: [a] -> Int -- | <math>. 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, ...]
--   
-- -- this means that map id == id -- --

Examples

-- --
--   >>> map (+1) [1, 2, 3]
--   [2,3,4]
--   
-- --
--   >>> map id [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> map (\n -> 3 * n + 1) [1, 2, 3]
--   [4,7,10]
--   
map :: (a -> b) -> [a] -> [b] -- | <math>. reverse xs returns the elements of -- xs in reverse order. xs must be finite. -- --

Laziness

-- -- reverse is lazy in its elements. -- --
--   >>> head (reverse [undefined, 1])
--   1
--   
-- --
--   >>> reverse (1 : 2 : undefined)
--   *** Exception: Prelude.undefined
--   
-- --

Examples

-- --
--   >>> reverse []
--   []
--   
-- --
--   >>> reverse [42]
--   [42]
--   
-- --
--   >>> reverse [2,5,7]
--   [7,5,2]
--   
-- --
--   >>> reverse [1..]
--   * Hangs forever *
--   
reverse :: [a] -> [a] -- | <math>. The intersperse function takes an element and a -- list and `intersperses' that element between the elements of the list. -- --

Laziness

-- -- intersperse has the following properties -- --
--   >>> take 1 (intersperse undefined ('a' : undefined))
--   "a"
--   
-- --
--   >>> take 2 (intersperse ',' ('a' : undefined))
--   "a*** Exception: Prelude.undefined
--   
-- --

Examples

-- --
--   >>> intersperse ',' "abcde"
--   "a,b,c,d,e"
--   
-- --
--   >>> intersperse 1 [3, 4, 5]
--   [3,1,4,1,5]
--   
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. -- --

Laziness

-- -- intercalate has the following properties: -- --
--   >>> take 5 (intercalate undefined ("Lorem" : undefined))
--   "Lorem"
--   
-- --
--   >>> take 6 (intercalate ", " ("Lorem" : undefined))
--   "Lorem*** Exception: Prelude.undefined
--   
-- --

Examples

-- --
--   >>> intercalate ", " ["Lorem", "ipsum", "dolor"]
--   "Lorem, ipsum, dolor"
--   
-- --
--   >>> intercalate [0, 1] [[2, 3], [4, 5, 6], []]
--   [2,3,0,1,4,5,6,0,1]
--   
-- --
--   >>> intercalate [1, 2, 3] [[], []]
--   [1,2,3]
--   
intercalate :: [a] -> [[a]] -> [a] -- | The transpose function transposes the rows and columns of its -- argument. -- --

Laziness

-- -- transpose is lazy in its elements -- --
--   >>> take 1 (transpose ['a' : undefined, 'b' : undefined])
--   ["ab"]
--   
-- --

Examples

-- --
--   >>> 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]]
--   
-- -- For this reason the outer list must be finite; otherwise -- transpose hangs: -- --
--   >>> transpose (repeat [])
--   * Hangs forever *
--   
transpose :: [[a]] -> [[a]] -- | The subsequences function returns the list of all subsequences -- of the argument. -- --

Laziness

-- -- subsequences does not look ahead unless it must: -- --
--   >>> take 1 (subsequences undefined)
--   [[]]
--   
--   >>> take 2 (subsequences ('a' : undefined))
--   ["","a"]
--   
-- --

Examples

-- --
--   >>> subsequences "abc"
--   ["","a","b","ab","c","ac","bc","abc"]
--   
-- -- This function is productive on infinite inputs: -- --
--   >>> take 8 $ subsequences ['a'..]
--   ["","a","b","ab","c","ac","bc","abc"]
--   
subsequences :: [a] -> [[a]] -- | The permutations function returns the list of all permutations -- of the argument. -- -- Note that the order of permutations is not lexicographic. It satisfies -- the following property: -- --
--   map (take n) (take (product [1..n]) (permutations ([1..n] ++ undefined))) == permutations [1..n]
--   
-- --

Laziness

-- -- The permutations function is maximally lazy: for each -- n, the value of permutations xs starts with -- those permutations that permute take n xs and keep -- drop n xs. -- --

Examples

-- --
--   >>> permutations "abc"
--   ["abc","bac","cba","bca","cab","acb"]
--   
-- --
--   >>> permutations [1, 2]
--   [[1,2],[2,1]]
--   
-- --
--   >>> permutations []
--   [[]]
--   
-- -- This function is productive on infinite inputs: -- --
--   >>> take 6 $ map (take 3) $ permutations ['a'..]
--   ["abc","bac","cba","bca","cab","acb"]
--   
permutations :: [a] -> [[a]] -- | The sum function computes the sum of a finite list of numbers. -- --
--   >>> sum []
--   0
--   
--   >>> sum [42]
--   42
--   
--   >>> sum [1..10]
--   55
--   
--   >>> sum [4.1, 2.0, 1.7]
--   7.8
--   
--   >>> sum [1..]
--   * Hangs forever *
--   
sum :: Num a => [a] -> a -- | The product function computes the product of a finite list of -- numbers. -- --
--   >>> product []
--   1
--   
--   >>> product [42]
--   42
--   
--   >>> product [1..10]
--   3628800
--   
--   >>> product [4.1, 2.0, 1.7]
--   13.939999999999998
--   
--   >>> product [1..]
--   * Hangs forever *
--   
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 []
--   *** Exception: Prelude.maximum: empty list
--   
--   >>> maximum [42]
--   42
--   
--   >>> maximum [55, -12, 7, 0, -89]
--   55
--   
--   >>> maximum [1..]
--   * Hangs forever *
--   
maximum :: (Ord a, HasCallStack) => [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 []
--   *** Exception: Prelude.minimum: empty list
--   
--   >>> minimum [42]
--   42
--   
--   >>> minimum [55, -12, 7, 0, -89]
--   -89
--   
--   >>> minimum [1..]
--   * Hangs forever *
--   
minimum :: (Ord a, HasCallStack) => [a] -> a -- | <math>. 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
--   
-- --

Examples

-- --
--   >>> scanl (+) 0 [1..4]
--   [0,1,3,6,10]
--   
-- --
--   >>> scanl (+) 42 []
--   [42]
--   
-- --
--   >>> scanl (-) 100 [1..4]
--   [100,99,97,94,90]
--   
-- --
--   >>> scanl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   ["foo","afoo","bafoo","cbafoo","dcbafoo"]
--   
-- --
--   >>> take 10 (scanl (+) 0 [1..])
--   [0,1,3,6,10,15,21,28,36,45]
--   
-- --
--   >>> take 1 (scanl undefined 'a' undefined)
--   "a"
--   
scanl :: (b -> a -> b) -> b -> [a] -> [b] -- | <math>. A strict version of scanl. scanl' :: (b -> a -> b) -> b -> [a] -> [b] -- | <math>. scanl1 is a variant of scanl that has no -- starting value argument: -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
-- --

Examples

-- --
--   >>> scanl1 (+) [1..4]
--   [1,3,6,10]
--   
-- --
--   >>> scanl1 (+) []
--   []
--   
-- --
--   >>> scanl1 (-) [1..4]
--   [1,-1,-4,-8]
--   
-- --
--   >>> scanl1 (&&) [True, False, True, True]
--   [True,False,False,False]
--   
-- --
--   >>> scanl1 (||) [False, False, True, True]
--   [False,False,True,True]
--   
-- --
--   >>> take 10 (scanl1 (+) [1..])
--   [1,3,6,10,15,21,28,36,45,55]
--   
-- --
--   >>> take 1 (scanl1 undefined ('a' : undefined))
--   "a"
--   
scanl1 :: (a -> a -> a) -> [a] -> [a] -- | <math>. scanr is the right-to-left dual of scanl. -- Note that the order of parameters on the accumulating function are -- reversed compared to scanl. Also note that -- --
--   head (scanr f z xs) == foldr f z xs.
--   
-- --

Examples

-- --
--   >>> scanr (+) 0 [1..4]
--   [10,9,7,4,0]
--   
-- --
--   >>> scanr (+) 42 []
--   [42]
--   
-- --
--   >>> scanr (-) 100 [1..4]
--   [98,-97,99,-96,100]
--   
-- --
--   >>> scanr (\nextChar reversedString -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   ["abcdfoo","bcdfoo","cdfoo","dfoo","foo"]
--   
-- --
--   >>> force $ scanr (+) 0 [1..]
--   *** Exception: stack overflow
--   
scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | <math>. scanr1 is a variant of scanr that has no -- starting value argument. -- --

Examples

-- --
--   >>> scanr1 (+) [1..4]
--   [10,9,7,4]
--   
-- --
--   >>> scanr1 (+) []
--   []
--   
-- --
--   >>> scanr1 (-) [1..4]
--   [-2,3,-1,4]
--   
-- --
--   >>> scanr1 (&&) [True, False, True, True]
--   [False,False,True,True]
--   
-- --
--   >>> scanr1 (||) [True, True, False, False]
--   [True,True,False,False]
--   
-- --
--   >>> force $ scanr1 (+) [1..]
--   *** Exception: stack overflow
--   
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 does not force accumulator if it is unused: -- --
--   >>> take 1 (snd (mapAccumL (\_ x -> (undefined, x)) undefined ('a' : undefined)))
--   "a"
--   
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), ...]
--   
-- --

Laziness

-- -- Note that iterate is lazy, potentially leading to thunk -- build-up if the consumer doesn't force each iterate. See -- iterate' for a strict variant of this function. -- --
--   >>> take 1 $ iterate undefined 42
--   [42]
--   
-- --

Examples

-- --
--   >>> take 10 $ iterate not True
--   [True,False,True,False,True,False,True,False,True,False]
--   
-- --
--   >>> take 10 $ iterate (+3) 42
--   [42,45,48,51,54,57,60,63,66,69]
--   
-- -- iterate id == repeat: -- --
--   >>> take 10 $ iterate id 1
--   [1,1,1,1,1,1,1,1,1,1]
--   
iterate :: (a -> a) -> a -> [a] -- | iterate' is the strict version of iterate. -- -- It forces the result of each application of the function to weak head -- normal form (WHNF) before proceeding. -- --
--   >>> take 1 $ iterate' undefined 42
--   *** Exception: Prelude.undefined
--   
iterate' :: (a -> a) -> 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. -- --

Examples

-- --
--   >>> replicate 0 True
--   []
--   
-- --
--   >>> replicate (-1) True
--   []
--   
-- --
--   >>> replicate 4 True
--   [True,True,True,True]
--   
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. -- --

Examples

-- --
--   >>> cycle []
--   *** Exception: Prelude.cycle: empty list
--   
-- --
--   >>> take 10 (cycle [42])
--   [42,42,42,42,42,42,42,42,42,42]
--   
-- --
--   >>> take 10 (cycle [2, 5, 7])
--   [2,5,7,2,5,7,2,5,7,2]
--   
-- --
--   >>> take 1 (cycle (42 : undefined))
--   [42]
--   
cycle :: HasCallStack => [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
--   
-- --

Laziness

-- --
--   >>> take 1 (unfoldr (\x -> Just (x, undefined)) 'a')
--   "a"
--   
-- --

Examples

-- --
--   >>> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
--   [10,9,8,7,6,5,4,3,2,1]
--   
-- --
--   >>> take 10 $ unfoldr (\(x, y) -> Just (x, (y, x + y))) (0, 1)
--   [0,1,1,2,3,5,8,13,21,54]
--   
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. -- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. -- --

Laziness

-- --
--   >>> take 0 undefined
--   []
--   
--   >>> take 2 (1 : 2 : undefined)
--   [1,2]
--   
-- --

Examples

-- --
--   >>> 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]
--   []
--   
take :: 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 is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. -- --

Laziness

-- -- It is equivalent to (take n xs, drop n xs) -- unless n is _|_: splitAt _|_ xs = _|_, not -- (_|_, _|_)). -- -- The first component of the tuple is produced lazily: -- --
--   >>> fst (splitAt 0 undefined)
--   []
--   
-- --
--   >>> take 1 (fst (splitAt 10 (1 : undefined)))
--   [1]
--   
-- --

Examples

-- --
--   >>> 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])
--   
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. -- --

Laziness

-- --
--   >>> takeWhile (const False) undefined
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> takeWhile (const False) (undefined : undefined)
--   []
--   
-- --
--   >>> take 1 (takeWhile (const True) (1 : undefined))
--   [1]
--   
-- --

Examples

-- --
--   >>> 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. -- --

Examples

-- --
--   >>> 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. -- --

Laziness

-- -- This function is lazy in spine, but strict in elements, which makes it -- different from reverse . dropWhile p -- . reverse, which is strict in spine, but lazy in -- elements. For instance: -- --
--   >>> take 1 (dropWhileEnd (< 0) (1 : undefined))
--   [1]
--   
-- --
--   >>> take 1 (reverse $ dropWhile (< 0) $ reverse (1 : undefined))
--   *** Exception: Prelude.undefined
--   
-- -- but on the other hand -- --
--   >>> last (dropWhileEnd (< 0) [undefined, 1])
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> last (reverse $ dropWhile (< 0) $ reverse [undefined, 1])
--   1
--   
-- --

Examples

-- --
--   >>> dropWhileEnd isSpace "foo\n"
--   "foo"
--   
-- --
--   >>> dropWhileEnd isSpace "foo bar"
--   "foo bar"
--   
--   >>> dropWhileEnd (> 10) [1..20]
--   [1,2,3,4,5,6,7,8,9,10]
--   
dropWhileEnd :: (a -> Bool) -> [a] -> [a] -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is the longest prefix (possibly -- empty) of xs of elements that satisfy p and second -- element is the remainder of the list: -- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs), even if p is _|_. -- --

Laziness

-- --
--   >>> span undefined []
--   ([],[])
--   
--   >>> fst (span (const False) undefined)
--   *** Exception: Prelude.undefined
--   
--   >>> fst (span (const False) (undefined : undefined))
--   []
--   
--   >>> take 1 (fst (span (const True) (1 : undefined)))
--   [1]
--   
-- -- span produces the first component of the tuple lazily: -- --
--   >>> take 10 (fst (span (const True) [1..]))
--   [1,2,3,4,5,6,7,8,9,10]
--   
-- --

Examples

-- --
--   >>> 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 :: (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 p is equivalent to span (not . -- p) and consequently to (takeWhile (not . p) xs, -- dropWhile (not . p) xs), even if p is -- _|_. -- --

Laziness

-- --
--   >>> break undefined []
--   ([],[])
--   
-- --
--   >>> fst (break (const True) undefined)
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> fst (break (const True) (undefined : undefined))
--   []
--   
-- --
--   >>> take 1 (fst (break (const False) (1 : undefined)))
--   [1]
--   
-- -- break produces the first component of the tuple lazily: -- --
--   >>> take 10 (fst (break (const False) [1..]))
--   [1,2,3,4,5,6,7,8,9,10]
--   
-- --

Examples

-- --
--   >>> 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 :: (a -> Bool) -> [a] -> ([a], [a]) -- | <math>. 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. -- --
Examples
-- --
--   >>> 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 inits function returns all initial segments of the -- argument, shortest first. -- -- inits is semantically equivalent to map -- reverse . scanl (flip (:)) [], but under the -- hood uses a queue to amortize costs of reverse. -- --

Laziness

-- -- Note that inits has the following strictness property: -- inits (xs ++ _|_) = inits xs ++ _|_ -- -- In particular, inits _|_ = [] : _|_ -- --

Examples

-- --
--   >>> inits "abc"
--   ["","a","ab","abc"]
--   
-- --
--   >>> inits []
--   [[]]
--   
-- -- inits is productive on infinite lists: -- --
--   >>> take 5 $ inits [1..]
--   [[],[1],[1,2],[1,2,3],[1,2,3,4]]
--   
inits :: [a] -> [[a]] -- | <math>. The tails function returns all final segments of -- the argument, longest first. -- --

Laziness

-- -- Note that tails has the following strictness property: -- tails _|_ = _|_ : _|_ -- --
--   >>> tails undefined
--   [*** Exception: Prelude.undefined
--   
-- --
--   >>> drop 1 (tails [undefined, 1, 2])
--   [[1, 2], [2], []]
--   
-- --

Examples

-- --
--   >>> tails "abc"
--   ["abc","bc","c",""]
--   
-- --
--   >>> tails [1, 2, 3]
--   [[1,2,3],[2,3],[3],[]]
--   
-- --
--   >>> tails []
--   [[]]
--   
tails :: [a] -> [[a]] -- | <math>. The isPrefixOf function takes two lists and -- returns True iff the first list is a prefix of the second. -- --

Examples

-- --
--   >>> "Hello" `isPrefixOf` "Hello World!"
--   True
--   
-- --
--   >>> "Hello" `isPrefixOf` "Wello Horld!"
--   False
--   
-- -- For the result to be True, the first list must be finite; -- False, however, results from any mismatch: -- --
--   >>> [0..] `isPrefixOf` [1..]
--   False
--   
-- --
--   >>> [0..] `isPrefixOf` [0..99]
--   False
--   
-- --
--   >>> [0..99] `isPrefixOf` [0..]
--   True
--   
-- --
--   >>> [0..] `isPrefixOf` [0..]
--   * Hangs forever *
--   
-- -- isPrefixOf shortcuts when the first argument is empty: -- --
--   >>> isPrefixOf [] undefined
--   True
--   
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. -- --

Examples

-- --
--   >>> "ld!" `isSuffixOf` "Hello World!"
--   True
--   
-- --
--   >>> "World" `isSuffixOf` "Hello World!"
--   False
--   
-- -- The second list must be finite; however the first list may be -- infinite: -- --
--   >>> [0..] `isSuffixOf` [0..99]
--   False
--   
-- --
--   >>> [0..99] `isSuffixOf` [0..]
--   * Hangs forever *
--   
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. -- --

Examples

-- --
--   >>> isInfixOf "Haskell" "I really like Haskell."
--   True
--   
-- --
--   >>> isInfixOf "Ial" "I really like Haskell."
--   False
--   
-- -- For the result to be True, the first list must be finite; for -- the result to be False, the second list must be finite: -- --
--   >>> [20..50] `isInfixOf` [0..]
--   True
--   
-- --
--   >>> [0..] `isInfixOf` [20..50]
--   False
--   
-- --
--   >>> [0..] `isInfixOf` [0..]
--   * Hangs forever *
--   
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. -- --

Examples

-- --
--   >>> 3 `elem` []
--   False
--   
-- --
--   >>> 3 `elem` [1,2]
--   False
--   
-- --
--   >>> 3 `elem` [1,2,3,4,5]
--   True
--   
-- --
--   >>> 3 `elem` [1..]
--   True
--   
-- --
--   >>> 3 `elem` [4..]
--   * Hangs forever *
--   
elem :: Eq a => a -> [a] -> Bool infix 4 `elem` -- | <math>. lookup key assocs looks up a key in an -- association list. For the result to be Nothing, the list must -- be finite. -- --

Examples

-- --
--   >>> lookup 2 []
--   Nothing
--   
-- --
--   >>> lookup 2 [(1, "first")]
--   Nothing
--   
-- --
--   >>> lookup 2 [(1, "first"), (2, "second"), (3, "third")]
--   Just "second"
--   
lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | <math>. 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]
--   
-- --

Examples

-- --
--   >>> filter odd [1, 2, 3]
--   [1,3]
--   
-- --
--   >>> filter (\l -> length l > 3) ["Hello", ", ", "World", "!"]
--   ["Hello","World"]
--   
-- --
--   >>> filter (/= 3) [1, 2, 3, 4, 3, 2, 1]
--   [1,2,4,2,1]
--   
filter :: (a -> Bool) -> [a] -> [a] -- | The partition function takes a predicate and 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)
--   
-- --

Examples

-- --
--   >>> partition (`elem` "aeiou") "Hello World!"
--   ("eoo","Hll Wrld!")
--   
-- --
--   >>> partition even [1..10]
--   ([2,4,6,8,10],[1,3,5,7,9])
--   
-- --
--   >>> partition (< 5) [1..10]
--   ([1,2,3,4],[5,6,7,8,9,10])
--   
partition :: (a -> Bool) -> [a] -> ([a], [a]) -- | List index (subscript) operator, starting from 0. Returns -- Nothing if the index is out of bounds -- -- This is the total variant of the partial !! operator. -- -- WARNING: This function takes linear time in the index. -- --

Examples

-- --
--   >>> ['a', 'b', 'c'] !? 0
--   Just 'a'
--   
-- --
--   >>> ['a', 'b', 'c'] !? 2
--   Just 'c'
--   
-- --
--   >>> ['a', 'b', 'c'] !? 3
--   Nothing
--   
-- --
--   >>> ['a', 'b', 'c'] !? (-1)
--   Nothing
--   
(!?) :: [a] -> Int -> Maybe a infixl 9 !? -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. -- -- WARNING: This function is partial, and should only be used if you are -- sure that the indexing will not fail. Otherwise, use !?. -- -- WARNING: This function takes linear time in the index. -- --

Examples

-- --
--   >>> ['a', 'b', 'c'] !! 0
--   'a'
--   
-- --
--   >>> ['a', 'b', 'c'] !! 2
--   'c'
--   
-- --
--   >>> ['a', 'b', 'c'] !! 3
--   *** Exception: Prelude.!!: index too large
--   
-- --
--   >>> ['a', 'b', 'c'] !! (-1)
--   *** Exception: Prelude.!!: negative index
--   
(!!) :: HasCallStack => [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. For the result to be -- Nothing, the list must be finite. -- --

Examples

-- --
--   >>> elemIndex 4 [0..]
--   Just 4
--   
-- --
--   >>> elemIndex 'o' "haskell"
--   Nothing
--   
-- --
--   >>> elemIndex 0 [1..]
--   * hangs forever *
--   
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. -- --

Examples

-- --
--   >>> elemIndices 'o' "Hello World"
--   [4,7]
--   
-- --
--   >>> elemIndices 1 [1, 2, 3, 1, 2, 3]
--   [0,3]
--   
elemIndices :: Eq a => a -> [a] -> [Int] -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. -- --

Examples

-- --
--   >>> findIndices (`elem` "aeiou") "Hello World!"
--   [1,4,7]
--   
-- --
--   >>> findIndices (\l -> length l > 3) ["a", "bcde", "fgh", "ijklmnop"]
--   [1,3]
--   
findIndices :: (a -> Bool) -> [a] -> [Int] -- | <math>. zip takes two lists and returns a list of -- corresponding pairs. -- -- zip is right-lazy: -- --
--   >>> zip [] undefined
--   []
--   
--   >>> zip undefined []
--   *** Exception: Prelude.undefined
--   ...
--   
-- -- zip is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. -- --

Examples

-- --
--   >>> zip [1, 2, 3] ['a', 'b', 'c']
--   [(1,'a'),(2,'b'),(3,'c')]
--   
-- -- If one input list is shorter than the other, excess elements of the -- longer list are discarded, even if one of the lists is infinite: -- --
--   >>> zip [1] ['a', 'b']
--   [(1,'a')]
--   
-- --
--   >>> zip [1, 2] ['a']
--   [(1,'a')]
--   
-- --
--   >>> zip [] [1..]
--   []
--   
-- --
--   >>> zip [1..] []
--   []
--   
zip :: [a] -> [b] -> [(a, b)] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. It is capable of list fusion, but it is restricted to -- its first list argument and its resulting list. zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] -- | The zip4 function takes four lists and returns a list of -- quadruples, analogous to zip. It is capable of list fusion, but -- it is restricted to its first list argument and its resulting list. 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. It is capable of list fusion, -- but it is restricted to its first list argument and its resulting -- list. 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. It is capable of list fusion, but -- it is restricted to its first list argument and its resulting list. 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. It is capable of list fusion, -- but it is restricted to its first list argument and its resulting -- list. zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)] -- | <math>. The zipWith3 function takes a function which -- combines three elements, as well as three lists and returns a list of -- the function applied to corresponding elements, analogous to -- zipWith. It is capable of list fusion, but it is restricted to -- its first list argument and its resulting list. -- --
--   zipWith3 (,,) xs ys zs == zip3 xs ys zs
--   zipWith3 f [x1,x2,x3..] [y1,y2,y3..] [z1,z2,z3..] == [f x1 y1 z1, f x2 y2 z2, f x3 y3 z3..]
--   
-- --

Examples

-- --
--   >>> zipWith3 (\x y z -> [x, y, z]) "123" "abc" "xyz"
--   ["1ax","2by","3cz"]
--   
-- --
--   >>> zipWith3 (\x y z -> (x * y) + z) [1, 2, 3] [4, 5, 6] [7, 8, 9]
--   [11,18,27]
--   
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. It is capable of list -- fusion, but it is restricted to its first list argument and its -- resulting list. 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. It is capable of list -- fusion, but it is restricted to its first list argument and its -- resulting list. 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. It is capable of list -- fusion, but it is restricted to its first list argument and its -- resulting list. 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. It is capable of -- list fusion, but it is restricted to its first list argument and its -- resulting list. zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -- | The unzip3 function takes a list of triples and returns three -- lists of the respective components, analogous to unzip. -- --

Examples

-- --
--   >>> unzip3 []
--   ([],[],[])
--   
-- --
--   >>> unzip3 [(1, 'a', True), (2, 'b', False)]
--   ([1,2],"ab",[True,False])
--   
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]) -- | Splits the argument into a list of lines stripped of their -- terminating \n characters. The \n terminator is -- optional in a final non-empty line of the argument string. -- -- When the argument string is empty, or ends in a \n character, -- it can be recovered by passing the result of lines to the -- unlines function. Otherwise, unlines appends the missing -- terminating \n. This makes unlines . lines -- idempotent: -- --
--   (unlines . lines) . (unlines . lines) = (unlines . lines)
--   
-- --

Examples

-- --
--   >>> lines ""           -- empty input contains no lines
--   []
--   
-- --
--   >>> lines "\n"         -- single empty line
--   [""]
--   
-- --
--   >>> lines "one"        -- single unterminated line
--   ["one"]
--   
-- --
--   >>> lines "one\n"      -- single non-empty line
--   ["one"]
--   
-- --
--   >>> lines "one\n\n"    -- second line is empty
--   ["one",""]
--   
-- --
--   >>> lines "one\ntwo"   -- second line is unterminated
--   ["one","two"]
--   
-- --
--   >>> lines "one\ntwo\n" -- two non-empty lines
--   ["one","two"]
--   
lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space (as defined by isSpace). This function -- trims any white spaces at the beginning and at the end. -- --

Examples

-- --
--   >>> words "Lorem ipsum\ndolor"
--   ["Lorem","ipsum","dolor"]
--   
-- --
--   >>> words " foo bar "
--   ["foo","bar"]
--   
words :: String -> [String] -- | Appends a \n character to each input string, then -- concatenates the results. Equivalent to foldMap (s -> -- s ++ "\n"). -- --

Examples

-- --
--   >>> unlines ["Hello", "World", "!"]
--   "Hello\nWorld\n!\n"
--   
-- -- Note that unlines . lines /= -- id when the input is not \n-terminated: -- --
--   >>> unlines . lines $ "foo\nbar"
--   "foo\nbar\n"
--   
unlines :: [String] -> String -- | unwords joins words with separating spaces (U+0020 SPACE). -- -- unwords is neither left nor right inverse of words: -- --
--   >>> words (unwords [" "])
--   []
--   
--   >>> unwords (words "foo\nbar")
--   "foo bar"
--   
-- --

Examples

-- --
--   >>> unwords ["Lorem", "ipsum", "dolor"]
--   "Lorem ipsum dolor"
--   
-- --
--   >>> unwords ["foo", "bar", "", "baz"]
--   "foo bar  baz"
--   
unwords :: [String] -> String -- | <math>. 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. -- -- If there exists instance Ord a, it's faster to use -- nubOrd from the containers package (link to the -- latest online documentation), which takes only <math> time -- where d is the number of distinct elements in the list. -- -- Another approach to speed up nub is to use map -- Data.List.NonEmpty.head . -- Data.List.NonEmpty.group . sort, which takes -- <math> time, requires instance Ord a and doesn't -- preserve the order. -- --

Examples

-- --
--   >>> nub [1,2,3,4,3,2,1,2,4,3,5]
--   [1,2,3,4,5]
--   
-- --
--   >>> nub "hello, world!"
--   "helo, wrd!"
--   
nub :: Eq a => [a] -> [a] -- | <math>. delete x removes the first occurrence of -- x from its list argument. -- -- It is a special case of deleteBy, which allows the programmer -- to supply their own equality test. -- --

Examples

-- --
--   >>> delete 'a' "banana"
--   "bnana"
--   
-- --
--   >>> delete "not" ["haskell", "is", "not", "awesome"]
--   ["haskell","is","awesome"]
--   
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. -- --

Examples

-- --
--   >>> "Hello World!" \\ "ell W"
--   "Hoorld!"
--   
-- -- The second list must be finite, but the first may be infinite. -- --
--   >>> take 5 ([0..] \\ [2..4])
--   [0,1,5,6,7]
--   
-- --
--   >>> take 5 ([0..] \\ [2..])
--   * Hangs forever *
--   
(\\) :: Eq a => [a] -> [a] -> [a] infix 5 \\ -- | The union function returns the list union of the two lists. It -- is a special case of unionBy, which allows the programmer to -- supply their own equality test. -- --

Examples

-- --
--   >>> "dog" `union` "cow"
--   "dogcw"
--   
-- -- If equal elements are present in both lists, an element from the first -- list will be used. If the second list contains equal elements, only -- the first one will be retained: -- --
--   >>> import Data.Semigroup(Arg(..))
--   
--   >>> union [Arg () "dog"] [Arg () "cow"]
--   [Arg () "dog"]
--   
--   >>> union [] [Arg () "dog", Arg () "cow"]
--   [Arg () "dog"]
--   
-- -- However if the first list contains duplicates, so will the result: -- --
--   >>> "coot" `union` "duck"
--   "cootduk"
--   
--   >>> "duck" `union` "coot"
--   "duckot"
--   
-- -- union is productive even if both arguments are infinite. -- --
--   >>> [0, 2 ..] `union` [1, 3 ..]
--   [0,2,4,6,8,10,12..
--   
union :: Eq a => [a] -> [a] -> [a] -- | The intersect function takes the list intersection of two -- lists. It is a special case of intersectBy, which allows the -- programmer to supply their own equality test. -- --
Examples
-- --
--   >>> [1,2,3,4] `intersect` [2,4,6,8]
--   [2,4]
--   
-- -- If equal elements are present in both lists, an element from the first -- list will be used, and all duplicates from the second list quashed: -- --
--   >>> import Data.Semigroup
--   
--   >>> intersect [Arg () "dog"] [Arg () "cow", Arg () "cat"]
--   [Arg () "dog"]
--   
-- -- However if the first list contains duplicates, so will the result. -- --
--   >>> "coot" `intersect` "heron"
--   "oo"
--   
--   >>> "heron" `intersect` "coot"
--   "o"
--   
-- -- If the second list is infinite, intersect either hangs or -- returns its first argument in full. Otherwise if the first list is -- infinite, intersect might be productive: -- --
--   >>> intersect [100..] [0..]
--   [100,101,102,103...
--   
--   >>> intersect [0] [1..]
--   * Hangs forever *
--   
--   >>> intersect [1..] [0]
--   * Hangs forever *
--   
--   >>> intersect (cycle [1..3]) [2]
--   [2,2,2,2...
--   
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 lowest to highest, keeping duplicates in -- the order they appeared in the input. -- -- The argument must be finite. -- --

Examples

-- --
--   >>> sort [1,6,4,3,2,5]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> sort "haskell"
--   "aehklls"
--   
-- --
--   >>> import Data.Semigroup(Arg(..))
--   
--   >>> sort [Arg ":)" 0, Arg ":D" 0, Arg ":)" 1, Arg ":3" 0, Arg ":D" 1]
--   [Arg ":)" 0,Arg ":)" 1,Arg ":3" 0,Arg ":D" 0,Arg ":D" 1]
--   
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 lowest to highest, keeping duplicates in -- the order they appeared in the input. -- -- The argument must be finite. -- --

Examples

-- --
--   >>> sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
--   [(1,"Hello"),(2,"world"),(4,"!")]
--   
-- --
--   >>> sortOn length ["jim", "creed", "pam", "michael", "dwight", "kevin"]
--   ["jim","pam","creed","kevin","dwight","michael"]
--   
sortOn :: Ord b => (a -> b) -> [a] -> [a] -- | <math>. 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. -- --

Examples

-- --
--   >>> insert (-1) [1, 2, 3]
--   [-1,1,2,3]
--   
-- --
--   >>> insert 'd' "abcefg"
--   "abcdefg"
--   
-- --
--   >>> insert 4 [1, 2, 3, 5, 6, 7]
--   [1,2,3,4,5,6,7]
--   
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. -- --

Examples

-- --
--   >>> nubBy (\x y -> mod x 3 == mod y 3) [1,2,4,5,6]
--   [1,2,6]
--   
-- --
--   >>> nubBy (/=) [2, 7, 1, 8, 2, 8, 1, 8, 2, 8]
--   [2,2,2]
--   
-- --
--   >>> nubBy (>) [1, 2, 3, 2, 1, 5, 4, 5, 3, 2]
--   [1,2,3,5,5]
--   
nubBy :: (a -> a -> Bool) -> [a] -> [a] -- | <math>. The deleteBy function behaves like delete, -- but takes a user-supplied equality predicate. -- --

Examples

-- --
--   >>> deleteBy (<=) 4 [1..10]
--   [1,2,3,5,6,7,8,9,10]
--   
-- --
--   >>> deleteBy (/=) 5 [5, 5, 4, 3, 5, 2]
--   [5,5,3,5,2]
--   
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. This is the non-overloaded version of -- (\\). -- --
--   (\\) == deleteFirstsBy (==)
--   
-- -- The second list must be finite, but the first may be infinite. -- --

Examples

-- --
--   >>> deleteFirstsBy (>) [1..10] [3, 4, 5]
--   [4,5,6,7,8,9,10]
--   
-- --
--   >>> deleteFirstsBy (/=) [1..10] [1, 3, 5]
--   [4,5,6,7,8,9,10]
--   
deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The unionBy function is the non-overloaded version of -- union. Both arguments may be infinite. -- --

Examples

-- --
--   >>> unionBy (>) [3, 4, 5] [1, 2, 3, 4, 5, 6]
--   [3,4,5,4,5,6]
--   
-- --
--   >>> import Data.Semigroup (Arg(..))
--   
--   >>> unionBy (/=) [Arg () "Saul"] [Arg () "Kim"]
--   [Arg () "Saul", Arg () "Kim"]
--   
unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The intersectBy function is the non-overloaded version of -- intersect. It is productive for infinite arguments only if the -- first one is a subset of the second. intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The groupBy function is the non-overloaded version of -- group. -- -- When a supplied relation is not transitive, it is important to -- remember that equality is checked against the first element in the -- group, not against the nearest neighbour: -- --
--   >>> groupBy (\a b -> b - a < 5) [0..19]
--   [[0,1,2,3,4],[5,6,7,8,9],[10,11,12,13,14],[15,16,17,18,19]]
--   
-- -- It's often preferable to use -- Data.List.NonEmpty.groupBy, which provides type-level -- guarantees of non-emptiness of inner lists. -- --

Examples

-- --
--   >>> groupBy (/=) [1, 1, 1, 2, 3, 1, 4, 4, 5]
--   [[1],[1],[1,2,3],[1,4,4,5]]
--   
-- --
--   >>> groupBy (>) [1, 3, 5, 1, 4, 2, 6, 5, 4]
--   [[1],[3],[5,1,4,2],[6,5,4]]
--   
-- --
--   >>> groupBy (const not) [True, False, True, False, False, False, True]
--   [[True,False],[True,False,False,False],[True]]
--   
groupBy :: (a -> a -> Bool) -> [a] -> [[a]] -- | The sortBy function is the non-overloaded version of -- sort. The argument must be finite. -- -- The supplied comparison relation is supposed to be reflexive and -- antisymmetric, otherwise, e. g., for _ _ -> GT, the -- ordered list simply does not exist. The relation is also expected to -- be transitive: if it is not then sortBy might fail to find an -- ordered permutation, even if it exists. -- --

Examples

-- --
--   >>> sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")]
--   [(1,"Hello"),(2,"world"),(4,"!")]
--   
sortBy :: (a -> a -> Ordering) -> [a] -> [a] -- | <math>. The non-overloaded version of insert. -- --

Examples

-- --
--   >>> insertBy (\x y -> compare (length x) (length y)) [1, 2] [[1], [1, 2, 3], [1, 2, 3, 4]]
--   [[1],[1,2],[1,2,3],[1,2,3,4]]
--   
insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] -- | <math>. 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. -- --

Examples

-- --
--   >>> genericLength [1, 2, 3] :: Int
--   3
--   
--   >>> genericLength [1, 2, 3] :: Float
--   3.0
--   
-- -- Users should take care to pick a return type that is wide enough to -- contain the full length of the list. If the width is insufficient, the -- overflow behaviour will depend on the (+) implementation in -- the selected Num instance. The following example overflows -- because the actual list length of 200 lies outside of the -- Int8 range of -128..127. -- --
--   >>> genericLength [1..200] :: Int8
--   -56
--   
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] -- | Class of data structures that can be folded to a summary value. module Data.Foldable -- | The Foldable class represents data structures that can be reduced to a -- summary value one element at a time. Strict left-associative folds are -- a good fit for space-efficient reduction, while lazy right-associative -- folds are a good fit for corecursive iteration, or for folds that -- short-circuit after processing an initial subsequence of the -- structure's elements. -- -- Instances can be derived automatically by enabling the -- DeriveFoldable extension. For example, a derived instance for -- a binary tree might be: -- --
--   {-# LANGUAGE DeriveFoldable #-}
--   data Tree a = Empty
--               | Leaf a
--               | Node (Tree a) a (Tree a)
--       deriving Foldable
--   
-- -- A more detailed description can be found in the Overview -- section of Data.Foldable#overview. -- -- For the class laws see the Laws section of -- Data.Foldable#laws. class Foldable (t :: Type -> Type) -- | Given a structure with elements whose type is a Monoid, combine -- them via the monoid's (<>) operator. This fold -- is right-associative and lazy in the accumulator. When you need a -- strict left-associative fold, use foldMap' instead, with -- id as the map. -- --

Examples

-- -- Basic usage: -- --
--   >>> fold [[1, 2, 3], [4, 5], [6], []]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> fold $ Node (Leaf (Sum 1)) (Sum 3) (Leaf (Sum 5))
--   Sum {getSum = 9}
--   
-- -- Folds of unbounded structures do not terminate when the monoid's -- (<>) operator is strict: -- --
--   >>> fold (repeat Nothing)
--   * Hangs forever *
--   
-- -- Lazy corecursive folds of unbounded structures are fine: -- --
--   >>> take 12 $ fold $ map (\i -> [i..i+2]) [0..]
--   [0,1,2,1,2,3,2,3,4,3,4,5]
--   
--   >>> sum $ take 4000000 $ fold $ map (\i -> [i..i+2]) [0..]
--   2666668666666
--   
fold :: (Foldable t, Monoid m) => t m -> m -- | Map each element of the structure into a monoid, and combine the -- results with (<>). This fold is -- right-associative and lazy in the accumulator. For strict -- left-associative folds consider foldMap' instead. -- --

Examples

-- -- Basic usage: -- --
--   >>> foldMap Sum [1, 3, 5]
--   Sum {getSum = 9}
--   
-- --
--   >>> foldMap Product [1, 3, 5]
--   Product {getProduct = 15}
--   
-- --
--   >>> foldMap (replicate 3) [1, 2, 3]
--   [1,1,1,2,2,2,3,3,3]
--   
-- -- When a Monoid's (<>) is lazy in its second -- argument, foldMap can return a result even from an unbounded -- structure. For example, lazy accumulation enables -- Data.ByteString.Builder to efficiently serialise large data -- structures and produce the output incrementally: -- --
--   >>> import qualified Data.ByteString.Lazy as L
--   
--   >>> import qualified Data.ByteString.Builder as B
--   
--   >>> let bld :: Int -> B.Builder; bld i = B.intDec i <> B.word8 0x20
--   
--   >>> let lbs = B.toLazyByteString $ foldMap bld [0..]
--   
--   >>> L.take 64 lbs
--   "0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24"
--   
foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | A left-associative variant of foldMap that is strict in the -- accumulator. Use this method for strict reduction when partial results -- are merged via (<>). -- --

Examples

-- -- Define a Monoid over finite bit strings under xor. Use -- it to strictly compute the xor of a list of Int -- values. -- --
--   >>> :set -XGeneralizedNewtypeDeriving
--   
--   >>> import Data.Bits (Bits, FiniteBits, xor, zeroBits)
--   
--   >>> import Data.Foldable (foldMap')
--   
--   >>> import Numeric (showHex)
--   
--   >>> 
--   
--   >>> newtype X a = X a deriving (Eq, Bounded, Enum, Bits, FiniteBits)
--   
--   >>> instance Bits a => Semigroup (X a) where X a <> X b = X (a `xor` b)
--   
--   >>> instance Bits a => Monoid    (X a) where mempty     = X zeroBits
--   
--   >>> 
--   
--   >>> let bits :: [Int]; bits = [0xcafe, 0xfeed, 0xdeaf, 0xbeef, 0x5411]
--   
--   >>> (\ (X a) -> showString "0x" . showHex a $ "") $ foldMap' X bits
--   "0x42"
--   
foldMap' :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | Right-associative fold of a structure, lazy in the accumulator. -- -- 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, given an -- operator lazy in its right argument, foldr can produce a -- terminating expression from an unbounded list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldr f z = foldr f z . toList
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> foldr (||) False [False, True, False]
--   True
--   
-- --
--   >>> foldr (||) False []
--   False
--   
-- --
--   >>> foldr (\c acc -> acc ++ [c]) "foo" ['a', 'b', 'c', 'd']
--   "foodcba"
--   
-- --
Infinite structures
-- -- ⚠️ Applying foldr to infinite structures usually doesn't -- terminate. -- -- It may still terminate under one of the following conditions: -- -- -- --
Short-circuiting
-- -- (||) short-circuits on True values, so the -- following terminates because there is a True value finitely far -- from the left side: -- --
--   >>> foldr (||) False (True : repeat False)
--   True
--   
-- -- But the following doesn't terminate: -- --
--   >>> foldr (||) False (repeat False ++ [True])
--   * Hangs forever *
--   
-- --
Laziness in the second argument
-- -- Applying foldr to infinite structures terminates when the -- operator is lazy in its second argument (the initial accumulator is -- never used in this case, and so could be left undefined, but -- [] is more clear): -- --
--   >>> take 5 $ foldr (\i acc -> i : fmap (+3) acc) [] (repeat 1)
--   [1,4,7,10,13]
--   
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | foldr' is a variant of foldr that performs strict -- reduction from right to left, i.e. starting with the right-most -- element. The input structure must be finite, otherwise -- foldr' runs out of space (diverges). -- -- If you want a strict right fold in constant space, you need a -- structure that supports faster than O(n) access to the -- right-most element, such as Seq from the containers -- package. -- -- This method does not run in constant space for structures such as -- lists that don't support efficient right-to-left iteration and so -- require O(n) space to perform right-to-left reduction. Use of -- this method with such a structure is a hint that the chosen structure -- may be a poor fit for the task at hand. If the order in which the -- elements are combined is not important, use foldl' instead. foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Left-associative fold of a structure, lazy in the accumulator. This is -- rarely what you want, but can work well for structures with efficient -- right-to-left sequencing and an operator that is lazy in its left -- argument. -- -- 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. Like all left-associative folds, -- foldl will diverge if given an infinite list. -- -- If you want an efficient strict left-fold, you probably want to use -- foldl' instead of foldl. The reason for this is that the -- 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
--   
-- --

Examples

-- -- The first example is a strict fold, which in practice is best -- performed with foldl'. -- --
--   >>> foldl (+) 42 [1,2,3,4]
--   52
--   
-- -- Though the result below is lazy, the input is reversed before -- prepending it to the initial accumulator, so corecursion begins only -- after traversing the entire input string. -- --
--   >>> foldl (\acc c -> c : acc) "abcd" "efgh"
--   "hgfeabcd"
--   
-- -- A left fold of a structure that is infinite on the right cannot -- terminate, even when for any finite input the fold just returns the -- initial accumulator: -- --
--   >>> foldl (\a _ -> a) 0 $ repeat 1
--   * Hangs forever *
--   
-- -- WARNING: When it comes to lists, you always want to use either -- foldl' or foldr instead. 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 structure to a single strict result (e.g. sum). -- -- 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. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. -- --

Examples

-- -- Basic usage: -- --
--   >>> foldr1 (+) [1..4]
--   10
--   
-- --
--   >>> foldr1 (+) []
--   Exception: Prelude.foldr1: empty list
--   
-- --
--   >>> foldr1 (+) Nothing
--   *** Exception: foldr1: empty structure
--   
-- --
--   >>> foldr1 (-) [1..4]
--   -2
--   
-- --
--   >>> foldr1 (&&) [True, False, True, True]
--   False
--   
-- --
--   >>> foldr1 (||) [False, False, True, True]
--   True
--   
-- --
--   >>> foldr1 (+) [1..]
--   * Hangs forever *
--   
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. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. -- --
--   foldl1 f = foldl1 f . toList
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> foldl1 (+) [1..4]
--   10
--   
-- --
--   >>> foldl1 (+) []
--   *** Exception: Prelude.foldl1: empty list
--   
-- --
--   >>> foldl1 (+) Nothing
--   *** Exception: foldl1: empty structure
--   
-- --
--   >>> foldl1 (-) [1..4]
--   -8
--   
-- --
--   >>> foldl1 (&&) [True, False, True, True]
--   False
--   
-- --
--   >>> foldl1 (||) [False, False, True, True]
--   True
--   
-- --
--   >>> foldl1 (+) [1..]
--   * Hangs forever *
--   
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a -- | List of elements of a structure, from left to right. If the entire -- list is intended to be reduced via a fold, just fold the structure -- directly bypassing the list. -- --

Examples

-- -- Basic usage: -- --
--   >>> toList Nothing
--   []
--   
-- --
--   >>> toList (Just 42)
--   [42]
--   
-- --
--   >>> toList (Left "foo")
--   []
--   
-- --
--   >>> toList (Node (Leaf 5) 17 (Node Empty 12 (Leaf 8)))
--   [5,17,12,8]
--   
-- -- For lists, toList is the identity: -- --
--   >>> toList [1, 2, 3]
--   [1,2,3]
--   
toList :: Foldable t => t a -> [a] -- | Test whether the structure is empty. The default implementation is -- Left-associative and lazy in both the initial element and the -- accumulator. Thus optimised for structures where the first element can -- be accessed in constant time. Structures where this is not the case -- should have a non-default implementation. -- --

Examples

-- -- Basic usage: -- --
--   >>> null []
--   True
--   
-- --
--   >>> null [1]
--   False
--   
-- -- null is expected to terminate even for infinite structures. The -- default implementation terminates provided the structure is bounded on -- the left (there is a leftmost element). -- --
--   >>> null [1..]
--   False
--   
null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation just counts elements starting with the -- leftmost. Instances for structures that can compute the element count -- faster than via element-by-element counting, should provide a -- specialised implementation. -- --

Examples

-- -- Basic usage: -- --
--   >>> length []
--   0
--   
-- --
--   >>> length ['a', 'b', 'c']
--   3
--   
--   >>> length [1..]
--   * Hangs forever *
--   
length :: Foldable t => t a -> Int -- | Does the element occur in the structure? -- -- Note: elem is often used in infix form. -- --

Examples

-- -- Basic usage: -- --
--   >>> 3 `elem` []
--   False
--   
-- --
--   >>> 3 `elem` [1,2]
--   False
--   
-- --
--   >>> 3 `elem` [1,2,3,4,5]
--   True
--   
-- -- For infinite structures, the default implementation of elem -- terminates if the sought-after value exists at a finite distance from -- the left side of the structure: -- --
--   >>> 3 `elem` [1..]
--   True
--   
-- --
--   >>> 3 `elem` ([4..] ++ [3])
--   * Hangs forever *
--   
elem :: (Foldable t, Eq a) => a -> t a -> Bool -- | The largest element of a non-empty structure. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. A structure that supports random access -- and maintains its elements in order should provide a specialised -- implementation to return the maximum in faster than linear time. -- --

Examples

-- -- Basic usage: -- --
--   >>> maximum [1..10]
--   10
--   
-- --
--   >>> maximum []
--   *** Exception: Prelude.maximum: empty list
--   
-- --
--   >>> maximum Nothing
--   *** Exception: maximum: empty structure
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. maximum :: (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. A structure that supports random access -- and maintains its elements in order should provide a specialised -- implementation to return the minimum in faster than linear time. -- --

Examples

-- -- Basic usage: -- --
--   >>> minimum [1..10]
--   1
--   
-- --
--   >>> minimum []
--   *** Exception: Prelude.minimum: empty list
--   
-- --
--   >>> minimum Nothing
--   *** Exception: minimum: empty structure
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. minimum :: (Foldable t, Ord a) => t a -> a -- | The sum function computes the sum of the numbers of a -- structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> sum []
--   0
--   
-- --
--   >>> sum [42]
--   42
--   
-- --
--   >>> sum [1..10]
--   55
--   
-- --
--   >>> sum [4.1, 2.0, 1.7]
--   7.8
--   
-- --
--   >>> sum [1..]
--   * Hangs forever *
--   
sum :: (Foldable t, Num a) => t a -> a -- | The product function computes the product of the numbers of a -- structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> product []
--   1
--   
-- --
--   >>> product [42]
--   42
--   
-- --
--   >>> product [1..10]
--   3628800
--   
-- --
--   >>> product [4.1, 2.0, 1.7]
--   13.939999999999998
--   
-- --
--   >>> product [1..]
--   * Hangs forever *
--   
product :: (Foldable t, Num a) => t a -> a infix 4 `elem` -- | Right-to-left monadic fold over the elements of a structure. -- -- Given a structure t with elements (a, b, c, ..., x, -- y), the result of a fold with an operator function f is -- equivalent to: -- --
--   foldrM f z t = do
--       yy <- f y z
--       xx <- f x yy
--       ...
--       bb <- f b cc
--       aa <- f a bb
--       return aa -- Just @return z@ when the structure is empty
--   
-- -- For a Monad m, given two functions f1 :: a -> m b -- and f2 :: b -> m c, their Kleisli composition (f1 -- >=> f2) :: a -> m c is defined by: -- --
--   (f1 >=> f2) a = f1 a >>= f2
--   
-- -- Another way of thinking about foldrM is that it amounts to an -- application to z of a Kleisli composition: -- --
--   foldrM f z t = f y >=> f x >=> ... >=> f b >=> f a $ z
--   
-- -- The monadic effects of foldrM are sequenced from right to -- left, and e.g. folds of infinite lists will diverge. -- -- If at some step the bind operator (>>=) -- short-circuits (as with, e.g., mzero in a MonadPlus), -- the evaluated effects will be from a tail of the element sequence. If -- you want to evaluate the monadic effects in left-to-right order, or -- perhaps be able to short-circuit after an initial sequence of -- elements, you'll need to use foldlM instead. -- -- If the monadic effects don't short-circuit, the outermost application -- of f is to the leftmost element a, so that, ignoring -- effects, the result looks like a right fold: -- --
--   a `f` (b `f` (c `f` (... (x `f` (y `f` z))))).
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> let f i acc = do { print i ; return $ i : acc }
--   
--   >>> foldrM f [] [0..3]
--   3
--   2
--   1
--   0
--   [0,1,2,3]
--   
foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b -- | Left-to-right monadic fold over the elements of a structure. -- -- Given a structure t with elements (a, b, ..., w, x, -- y), the result of a fold with an operator function f is -- equivalent to: -- --
--   foldlM f z t = do
--       aa <- f z a
--       bb <- f aa b
--       ...
--       xx <- f ww x
--       yy <- f xx y
--       return yy -- Just @return z@ when the structure is empty
--   
-- -- For a Monad m, given two functions f1 :: a -> m b -- and f2 :: b -> m c, their Kleisli composition (f1 -- >=> f2) :: a -> m c is defined by: -- --
--   (f1 >=> f2) a = f1 a >>= f2
--   
-- -- Another way of thinking about foldlM is that it amounts to an -- application to z of a Kleisli composition: -- --
--   foldlM f z t =
--       flip f a >=> flip f b >=> ... >=> flip f x >=> flip f y $ z
--   
-- -- The monadic effects of foldlM are sequenced from left to -- right. -- -- If at some step the bind operator (>>=) -- short-circuits (as with, e.g., mzero in a MonadPlus), -- the evaluated effects will be from an initial segment of the element -- sequence. If you want to evaluate the monadic effects in right-to-left -- order, or perhaps be able to short-circuit after processing a tail of -- the sequence of elements, you'll need to use foldrM instead. -- -- If the monadic effects don't short-circuit, the outermost application -- of f is to the rightmost element y, so that, -- ignoring effects, the result looks like a left fold: -- --
--   ((((z `f` a) `f` b) ... `f` w) `f` x) `f` y
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> let f a e = do { print e ; return $ e : a }
--   
--   >>> foldlM f [] [0..3]
--   0
--   1
--   2
--   3
--   [3,2,1,0]
--   
foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b -- | Map each element of a structure to an Applicative action, -- evaluate these actions from left to right, and ignore the results. For -- a version that doesn't ignore the results see traverse. -- -- traverse_ is just like mapM_, but generalised to -- Applicative actions. -- --

Examples

-- -- Basic usage: -- --
--   >>> traverse_ print ["Hello", "world", "!"]
--   "Hello"
--   "world"
--   "!"
--   
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. This is -- forM_ generalised to Applicative actions. -- -- for_ is just like forM_, but generalised to -- Applicative actions. -- --

Examples

-- -- Basic usage: -- --
--   >>> for_ [1..4] print
--   1
--   2
--   3
--   4
--   
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_ is just like sequence_, but generalised to -- Applicative actions. -- --

Examples

-- -- Basic usage: -- --
--   >>> sequenceA_ [print "Hello", print "world", print "!"]
--   "Hello"
--   "world"
--   "!"
--   
sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () -- | The sum of a collection of actions using (<|>), -- generalizing concat. -- -- asum is just like msum, but generalised to -- Alternative. -- --

Examples

-- -- Basic usage: -- --
--   >>> asum [Just "Hello", Nothing, Just "World"]
--   Just "Hello"
--   
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. -- -- mapM_ is just like traverse_, but specialised to monadic -- actions. 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. -- -- forM_ is just like for_, but specialised to monadic -- actions. 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. -- -- sequence_ is just like sequenceA_, but specialised to -- monadic actions. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | The sum of a collection of actions using (<|>), -- generalizing concat. -- -- msum is just like asum, but specialised to -- MonadPlus. -- --

Examples

-- -- Basic usage, using the MonadPlus instance for Maybe: -- --
--   >>> msum [Just "Hello", Nothing, Just "World"]
--   Just "Hello"
--   
msum :: (Foldable t, MonadPlus m) => t (m a) -> m a -- | The concatenation of all the elements of a container of lists. -- --

Examples

-- -- Basic usage: -- --
--   >>> concat (Just [1, 2, 3])
--   [1,2,3]
--   
-- --
--   >>> concat (Left 42)
--   []
--   
-- --
--   >>> concat [[1, 2, 3], [4, 5], [6], []]
--   [1,2,3,4,5,6]
--   
concat :: Foldable t => t [a] -> [a] -- | Map a function over all the elements of a container and concatenate -- the resulting lists. -- --

Examples

-- -- Basic usage: -- --
--   >>> concatMap (take 3) [[1..], [10..], [100..], [1000..]]
--   [1,2,3,10,11,12,100,101,102,1000,1001,1002]
--   
-- --
--   >>> concatMap (take 3) (Just [1..])
--   [1,2,3]
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> and []
--   True
--   
-- --
--   >>> and [True]
--   True
--   
-- --
--   >>> and [False]
--   False
--   
-- --
--   >>> and [True, True, False]
--   False
--   
-- --
--   >>> and (False : repeat True) -- Infinite list [False,True,True,True,...
--   False
--   
-- --
--   >>> and (repeat True)
--   * Hangs forever *
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> or []
--   False
--   
-- --
--   >>> or [True]
--   True
--   
-- --
--   >>> or [False]
--   False
--   
-- --
--   >>> or [True, True, False]
--   True
--   
-- --
--   >>> or (True : repeat False) -- Infinite list [True,False,False,False,...
--   True
--   
-- --
--   >>> or (repeat False)
--   * Hangs forever *
--   
or :: Foldable t => t Bool -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. -- --

Examples

-- -- Basic usage: -- --
--   >>> any (> 3) []
--   False
--   
-- --
--   >>> any (> 3) [1,2]
--   False
--   
-- --
--   >>> any (> 3) [1,2,3,4,5]
--   True
--   
-- --
--   >>> any (> 3) [1..]
--   True
--   
-- --
--   >>> any (> 3) [0, -1..]
--   * Hangs forever *
--   
any :: Foldable t => (a -> Bool) -> t a -> Bool -- | Determines whether all elements of the structure satisfy the -- predicate. -- --

Examples

-- -- Basic usage: -- --
--   >>> all (> 3) []
--   True
--   
-- --
--   >>> all (> 3) [1,2]
--   False
--   
-- --
--   >>> all (> 3) [1,2,3,4,5]
--   False
--   
-- --
--   >>> all (> 3) [1..]
--   False
--   
-- --
--   >>> all (> 3) [4..]
--   * Hangs forever *
--   
all :: Foldable t => (a -> Bool) -> t a -> Bool -- | The largest element of a non-empty structure with respect to the given -- comparison function. -- --

Examples

-- -- Basic usage: -- --
--   >>> maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
--   "Longest"
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | The least element of a non-empty structure with respect to the given -- comparison function. -- --

Examples

-- -- Basic usage: -- --
--   >>> minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
--   "!"
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | notElem is the negation of elem. -- --

Examples

-- -- Basic usage: -- --
--   >>> 3 `notElem` []
--   True
--   
-- --
--   >>> 3 `notElem` [1,2]
--   True
--   
-- --
--   >>> 3 `notElem` [1,2,3,4,5]
--   False
--   
-- -- For infinite structures, notElem terminates if the value exists -- at a finite distance from the left side of the structure: -- --
--   >>> 3 `notElem` [1..]
--   False
--   
-- --
--   >>> 3 `notElem` ([4..] ++ [3])
--   * Hangs forever *
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> find (> 42) [0, 5..]
--   Just 45
--   
-- --
--   >>> find (> 12) [1..7]
--   Nothing
--   
find :: Foldable t => (a -> Bool) -> t a -> Maybe a 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 f => Data.Foldable.Foldable (Data.Semigroup.Internal.Alt f) instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Data.Monoid.Ap f) instance Data.Foldable.Foldable (GHC.Arr.Array i) instance Data.Foldable.Foldable Data.Ord.Down instance Data.Foldable.Foldable Data.Semigroup.Internal.Dual instance Data.Foldable.Foldable (Data.Either.Either a) instance Data.Foldable.Foldable Data.Monoid.First instance Data.Foldable.Foldable (GHC.Generics.K1 i c) instance Data.Foldable.Foldable Data.Monoid.Last instance Data.Foldable.Foldable [] instance Data.Foldable.Foldable f => Data.Foldable.Foldable (GHC.Generics.M1 i c f) instance Data.Foldable.Foldable GHC.Maybe.Maybe instance Data.Foldable.Foldable GHC.Base.NonEmpty instance Data.Foldable.Foldable GHC.Generics.Par1 instance Data.Foldable.Foldable Data.Semigroup.Internal.Product instance Data.Foldable.Foldable Data.Proxy.Proxy instance Data.Foldable.Foldable f => Data.Foldable.Foldable (GHC.Generics.Rec1 f) instance Data.Foldable.Foldable GHC.Tuple.Prim.Solo instance Data.Foldable.Foldable Data.Semigroup.Internal.Sum instance Data.Foldable.Foldable ((,) a) instance Data.Foldable.Foldable GHC.Generics.U1 instance Data.Foldable.Foldable GHC.Generics.UAddr instance Data.Foldable.Foldable GHC.Generics.UChar instance Data.Foldable.Foldable GHC.Generics.UDouble instance Data.Foldable.Foldable GHC.Generics.UFloat instance Data.Foldable.Foldable GHC.Generics.UInt instance Data.Foldable.Foldable GHC.Generics.UWord instance Data.Foldable.Foldable GHC.Generics.V1 module Data.Functor.Const -- | The Const functor. newtype Const a (b :: k) Const :: a -> Const a (b :: k) [getConst] :: Const a (b :: k) -> a instance GHC.Base.Monoid m => GHC.Base.Applicative (Data.Functor.Const.Const m) instance forall a k (b :: k). GHC.Bits.Bits a => GHC.Bits.Bits (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). GHC.Enum.Enum a => GHC.Enum.Enum (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.Bits.FiniteBits a => GHC.Bits.FiniteBits (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 Data.Foldable.Foldable (Data.Functor.Const.Const m) instance forall a k (b :: k). GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Const.Const a b) instance GHC.Base.Functor (Data.Functor.Const.Const m) 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.Integral a => GHC.Real.Integral (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Ix.Ix a => GHC.Ix.Ix (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.Num.Num a => GHC.Num.Num (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 k a (b :: k). GHC.Read.Read a => GHC.Read.Read (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.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.Base.Semigroup a => GHC.Base.Semigroup (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 forall a k (b :: k). Foreign.Storable.Storable a => Foreign.Storable.Storable (Data.Functor.Const.Const a b) -- | 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. -- -- The StablePtr 0 is reserved for representing NULL in foreign -- code. -- -- A value of type StablePtr a is a stable pointer to a Haskell -- expression of type a. data 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 -- newStablePtr. 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 -- might 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 -- | Legacy interface for arrays of arrays. Deprecated, because the -- Array# type can now store arrays directly. Consider simply -- using Array# instead of ArrayArray#. -- -- Use GHC.Exts instead of importing this module directly. module GHC.ArrayArray newtype ArrayArray# :: UnliftedType ArrayArray# :: Array# ByteArray# -> ArrayArray# newtype MutableArrayArray# s :: UnliftedType MutableArrayArray# :: MutableArray# s ByteArray# -> MutableArrayArray# s -- | Create a new mutable array of arrays with the specified number of -- elements, in the specified state thread, with each element recursively -- referring to the newly created array. newArrayArray# :: Int# -> State# s -> (# State# s, MutableArrayArray# s #) -- | Make a mutable array of arrays immutable, without copying. unsafeFreezeArrayArray# :: MutableArrayArray# s -> State# s -> (# State# s, ArrayArray# #) -- | Return the number of elements in the array. sizeofArrayArray# :: ArrayArray# -> Int# -- | Return the number of elements in the array. sizeofMutableArrayArray# :: MutableArrayArray# s -> Int# indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray# indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray# readByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, ByteArray# #) readMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, MutableByteArray# s #) readArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, ArrayArray# #) readMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, MutableArrayArray# s #) writeByteArrayArray# :: MutableArrayArray# s -> Int# -> ByteArray# -> State# s -> State# s writeMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> MutableByteArray# s -> State# s -> State# s writeArrayArrayArray# :: MutableArrayArray# s -> Int# -> ArrayArray# -> State# s -> State# s writeMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> State# s -> State# s -- | Copy a range of the ArrayArray# to the specified region in the -- MutableArrayArray#. Both arrays must fully contain the -- specified ranges, but this is not checked. The two arrays must not be -- the same array in different states, but this is not checked either. copyArrayArray# :: ArrayArray# -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s -- | Copy a range of the first MutableArrayArray# to the specified region -- in the second MutableArrayArray#. Both arrays must fully contain the -- specified ranges, but this is not checked. The regions are allowed to -- overlap, although this is only possible when the same array is -- provided as both the source and the destination. copyMutableArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s -- | Compare the underlying pointers of two arrays of arrays. sameArrayArray# :: ArrayArray# -> ArrayArray# -> Int# -- | Compare the underlying pointers of two mutable arrays of arrays. sameMutableArrayArray# :: MutableArrayArray# s -> MutableArrayArray# s -> Int# -- | 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 :: forall {k} (a :: k). Typeable a => TypeRep a -- | Use a TypeRep as Typeable evidence. -- -- The TypeRep pattern synonym brings a Typeable constraint -- into scope and can be used in place of withTypeable. -- --
--   f :: TypeRep a -> ..
--   f rep = withTypeable {- Typeable a in scope -}
--   
--   f :: TypeRep a -> ..
--   f TypeRep = {- Typeable a in scope -}
--   
withTypeable :: forall k (a :: k) 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 :: k) :~: (b :: k) [Refl] :: forall {k} (a :: k). a :~: a infix 4 :~: -- | 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] :: forall {k1} (a :: k1). a :~~: a infix 4 :~~: -- | TypeRep is a concrete representation of a (monomorphic) type. -- TypeRep supports reasonably efficient equality. See Note [Grand -- plan for Typeable] in GHC.Tc.Instance.Typeable data TypeRep (a :: k) -- | A explicitly bidirectional pattern synonym to construct a concrete -- representation of a type. -- -- As an expression: Constructs a singleton TypeRep a -- given a implicit 'Typeable a' constraint: -- --
--   TypeRep @a :: Typeable a => TypeRep a
--   
-- -- As a pattern: Matches on an explicit TypeRep a witness -- bringing an implicit Typeable a constraint into scope. -- --
--   f :: TypeRep a -> ..
--   f TypeRep = {- Typeable a in scope -}
--   
pattern TypeRep :: () => Typeable a => TypeRep a typeOf :: Typeable a => a -> TypeRep a -- | A type application. -- -- For instance, -- --
--   typeRep @(Maybe Int) === App (typeRep @Maybe) (typeRep @Int)
--   
-- -- Note that this will also match a function type, -- --
--   typeRep @(Int# -> Char)
--     ===
--   App (App arrow (typeRep @Int#)) (typeRep @Char)
--   
-- -- where arrow :: TypeRep ((->) :: TYPE IntRep -> Type -> -- Type). pattern App :: forall k2 t k1 a b. () => t ~ a b => TypeRep a -> TypeRep b -> TypeRep t -- | Pattern match on a type constructor pattern Con :: () => NotApplication a => TyCon -> TypeRep a -- | Pattern match on a type constructor including its instantiated kind -- variables. -- -- For instance, -- --
--   App (Con' proxyTyCon ks) intRep = typeRep @(Proxy @Int)
--   
-- -- will bring into scope, -- --
--   proxyTyCon :: TyCon
--   ks         == [someTypeRep Type] :: [SomeTypeRep]
--   intRep     == typeRep Int
--   
pattern Con' :: () => NotApplication a => TyCon -> [SomeTypeRep] -> TypeRep a -- | The function type constructor. -- -- For instance, -- --
--   typeRep @(Int -> Char) === Fun (typeRep @Int) (typeRep @Char)
--   
pattern Fun :: forall k fun (r1 :: RuntimeRep) (r2 :: RuntimeRep) arg res. () => (k ~ Type, fun ~~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun -- | Observe the type constructor of a type representation typeRepTyCon :: forall {k} (a :: k). TypeRep a -> TyCon -- | Helper to fully evaluate TypeRep for use as -- NFData(rnf) implementation rnfTypeRep :: forall {k} (a :: k). TypeRep a -> () -- | Type equality eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Maybe (a :~~: b) -- | Type equality decision decTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Either ((a :~~: b) -> Void) (a :~~: b) -- | Observe the kind of a type. typeRepKind :: forall k (a :: k). TypeRep a -> TypeRep k splitApps :: forall {k} (a :: k). 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 {k} proxy (a :: k). 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.10, all types automatically have Typeable instances -- derived. This is in contrast to previous releases where -- Typeable had to be explicitly derived using the -- DeriveDataTypeable language extension. -- -- 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 :: Typeable a => a -> TypeRep -- | Takes a value of type a and returns a concrete representation -- of that type. typeRep :: forall {k} proxy (a :: k). 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 :: k) :~: (b :: k) [Refl] :: forall {k} (a :: k). a :~: a infix 4 :~: -- | 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] :: forall {k1} (a :: k1). a :~~: a infix 4 :~~: -- | The type-safe cast operation cast :: (Typeable a, Typeable b) => a -> Maybe b -- | Extract a witness of equality of two types eqT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) -- | Extract a witness of heterogeneous equality of two types heqT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => Maybe (a :~~: b) -- | Decide an equality of two types decT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Either ((a :~: b) -> Void) (a :~: b) -- | Decide heterogeneous equality of two types. hdecT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => Either ((a :~~: b) -> Void) (a :~~: b) -- | A flexible variation parameterised in a type constructor gcast :: forall {k} (a :: k) (b :: k) c. (Typeable a, Typeable b) => c a -> Maybe (c b) -- | Cast over k1 -> k2 gcast1 :: forall {k1} {k2} c (t :: k2 -> k1) (t' :: k2 -> k1) (a :: k2). (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a)) -- | Cast over k1 -> k2 -> k3 gcast2 :: forall {k1} {k2} {k3} c (t :: k2 -> k3 -> k1) (t' :: k2 -> k3 -> k1) (a :: k2) (b :: k3). (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b)) -- | Proxy is a type that holds no data, but has a phantom parameter -- of arbitrary type (or even kind). Its use is to provide type -- information, even though there is no value available of that type (or -- it may be too costly to create one). -- -- Historically, Proxy :: Proxy a is a safer -- alternative to the undefined :: a idiom. -- --
--   >>> Proxy :: Proxy (Void, Int -> Int)
--   Proxy
--   
-- -- Proxy can even hold types of higher kinds, -- --
--   >>> Proxy :: Proxy Either
--   Proxy
--   
-- --
--   >>> Proxy :: Proxy Functor
--   Proxy
--   
-- --
--   >>> Proxy :: Proxy complicatedStructure
--   Proxy
--   
data Proxy (t :: k) Proxy :: Proxy (t :: k) -- | 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 :: Typeable t => t a -> TypeRep typeOf2 :: Typeable t => t a b -> TypeRep typeOf3 :: Typeable t => t a b c -> TypeRep typeOf4 :: Typeable t => t a b c d -> TypeRep typeOf5 :: Typeable t => t a b c d e -> TypeRep typeOf6 :: Typeable t => t a b c d e f -> TypeRep typeOf7 :: Typeable t => t a b c d e f g -> TypeRep trLiftedRep :: TypeRep LiftedRep -- | Exceptions and exception-handling functions. module GHC.Exception.Type -- | 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 -- | 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 -- | Arithmetic exceptions. data ArithException Overflow :: ArithException Underflow :: ArithException LossOfPrecision :: ArithException DivideByZero :: ArithException Denormal :: ArithException RatioZeroDenominator :: ArithException divZeroException :: SomeException overflowException :: SomeException ratioZeroDenomException :: SomeException underflowException :: SomeException instance GHC.Classes.Eq GHC.Exception.Type.ArithException instance GHC.Exception.Type.Exception GHC.Exception.Type.ArithException instance GHC.Exception.Type.Exception GHC.Exception.Type.SomeException instance GHC.Exception.Type.Exception GHC.Base.Void instance GHC.Classes.Ord GHC.Exception.Type.ArithException instance GHC.Show.Show GHC.Exception.Type.ArithException instance GHC.Show.Show GHC.Exception.Type.SomeException -- | Exceptions and exception-handling functions. module GHC.Exception -- | Throw an exception. Exceptions may be thrown from purely functional -- code, but may only be caught within the IO monad. -- -- WARNING: You may want to use throwIO instead so that your -- pure code stays exception-free. throw :: forall a e. Exception e => e -> a -- | This is thrown when the user calls error. The first -- String is the argument given to error, second -- String is the location. data ErrorCall ErrorCallWithLocation :: String -> String -> ErrorCall pattern ErrorCall :: String -> ErrorCall errorCallException :: String -> SomeException errorCallWithCallStackException :: String -> CallStack -> SomeException -- | 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 -- --
--   putStrLnWithCallStack :: HasCallStack => String -> IO ()
--   
-- -- as a variant of putStrLn that will get its call-site and -- print it, along with the string given as argument. We can access the -- call-stack inside putStrLnWithCallStack with -- callStack. -- --
--   >>> :{
--   putStrLnWithCallStack :: HasCallStack => String -> IO ()
--   putStrLnWithCallStack msg = do
--     putStrLn msg
--     putStrLn (prettyCallStack callStack)
--   :}
--   
-- -- Thus, if we call putStrLnWithCallStack we will get a -- formatted call-stack alongside our string. -- --
--   >>> putStrLnWithCallStack "hello"
--   hello
--   CallStack (from HasCallStack):
--     putStrLnWithCallStack, called at <interactive>:... in interactive:Ghci...
--   
-- -- 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 -- | 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)] -- | Pretty print a CallStack. prettyCallStack :: CallStack -> String prettyCallStackLines :: CallStack -> [String] showCCSStack :: [String] -> [String] -- | 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 instance GHC.Classes.Eq GHC.Exception.ErrorCall instance GHC.Exception.Type.Exception GHC.Exception.ErrorCall instance GHC.Classes.Ord GHC.Exception.ErrorCall instance GHC.Show.Show GHC.Exception.ErrorCall -- | Definitions for the IO monad and its friends. module GHC.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. newtype IO a IO :: (State# RealWorld -> (# State# RealWorld, a #)) -> IO a unIO :: IO a -> State# RealWorld -> (# State# RealWorld, a #) liftIO :: IO a -> State# RealWorld -> STret RealWorld a mplusIO :: IO a -> IO a -> IO a -- | 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! -- -- WARNING: If you're looking for "a way to get a String from an -- 'IO String'", then unsafePerformIO is not the way to go. Learn -- about do-notation and the <- syntax element before you -- proceed. unsafePerformIO :: 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 -- | 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 -- | unsafeDupableInterleaveIO 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. -- -- The computation may be performed multiple times by different threads, -- possibly at the same time. To ensure that the computation is performed -- only once, use unsafeInterleaveIO instead. unsafeDupableInterleaveIO :: IO a -> IO a -- | Ensures that the suspensions under evaluation by the current thread -- are unique; that is, the current thread is not evaluating anything -- that is also under evaluation by another thread that has also executed -- noDuplicate. -- -- This operation is used in the definition of unsafePerformIO to -- prevent the IO action from being executed multiple times, which is -- usually undesirable. noDuplicate :: IO () -- | Embed a strict state thread 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 -- | Convert an IO action into an ST action. The type of the -- result is constrained to use a RealWorld state thread, and -- therefore the result cannot be passed to runST. ioToST :: IO a -> ST RealWorld a -- | Convert an IO action to an ST action. This relies on -- IO and ST having the same representation modulo the -- constraint on the state thread type parameter. 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 state thread type parameter. -- -- 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 -- | 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 -- | 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 propagated further up. If -- you call it again, you might get the opposite behaviour. This is ok, -- because catch is an IO computation. catch :: Exception e => IO a -> (e -> IO a) -> IO a -- | Catch an exception in the IO monad. -- -- Note that this function is strict in the action. That is, -- catchException undefined b == _|_. See for details. catchException :: Exception e => IO a -> (e -> IO a) -> IO a -- | Catch any Exception type in the IO monad. -- -- Note that this function is strict in the action. That is, -- catchAny undefined b == _|_. See for details. catchAny :: IO a -> (forall e. Exception e => e -> IO a) -> IO 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` ()  ===> throw e
--   throwIO e `seq` ()  ===> ()
--   
-- -- 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 operations, whereas -- throw does not. We say that throwIO throws *precise* -- exceptions and throw, error, etc. all throw *imprecise* -- exceptions. For example -- --
--   throw e + error "boom" ===> error "boom"
--   throw e + error "boom" ===> throw e
--   
-- -- are both valid reductions and the compiler may pick any (loop, even), -- whereas -- --
--   throwIO e >> error "boom" ===> throwIO e
--   
-- -- will always throw e when executed. -- -- See also the GHC wiki page on precise exceptions for a more -- technical introduction to how GHC optimises around precise vs. -- imprecise exceptions. throwIO :: Exception e => e -> IO 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 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 unsafeUnmask :: IO a -> IO a -- | 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 onException :: IO a -> IO b -> IO a bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c finally :: 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 mkUserError :: [Char] -> SomeException instance GHC.Classes.Eq GHC.IO.MaskingState instance GHC.Show.Show GHC.IO.MaskingState -- | The IORef type module GHC.IORef -- | A mutable variable in the IO monad. -- --
--   >>> import Data.IORef
--   
--   >>> r <- newIORef 0
--   
--   >>> readIORef r
--   0
--   
--   >>> writeIORef r 1
--   
--   >>> readIORef r
--   1
--   
--   >>> atomicWriteIORef r 2
--   
--   >>> readIORef r
--   2
--   
--   >>> modifyIORef' r (+ 1)
--   
--   >>> readIORef r
--   3
--   
--   >>> atomicModifyIORef' r (\a -> (a + 1, ()))
--   
--   >>> readIORef r
--   4
--   
-- -- See also STRef and MVar. newtype IORef a IORef :: STRef RealWorld a -> IORef a -- | Build a new IORef newIORef :: a -> IO (IORef a) -- | Read the value of an IORef. -- -- Beware that the CPU executing a thread can reorder reads or writes to -- independent locations. See Data.IORef#memmodel for more -- details. readIORef :: IORef a -> IO a -- | Write a new value into an IORef. -- -- This function does not create a memory barrier and can be reordered -- with other independent reads and writes within a thread, which may -- cause issues for multithreaded execution. In these cases, consider -- using atomicWriteIORef instead. See Data.IORef#memmodel -- for more details. writeIORef :: IORef a -> a -> IO () -- | Atomically apply a function to the contents of an IORef, -- installing its first component in the IORef and returning the -- old contents and the result of applying the function. The result of -- the function application (the pair) is not forced. As a result, this -- can lead to memory leaks. It is generally better to use -- atomicModifyIORef2. atomicModifyIORef2Lazy :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) -- | Atomically apply a function to the contents of an IORef, -- installing its first component in the IORef and returning the -- old contents and the result of applying the function. The result of -- the function application (the pair) is forced, but neither of its -- components is. atomicModifyIORef2 :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) -- | Atomically apply a function to the contents of an IORef and -- return the old and new values. The result of the function is not -- forced. As this can lead to a memory leak, it is usually better to use -- atomicModifyIORef'_. atomicModifyIORefLazy_ :: IORef a -> (a -> a) -> IO (a, a) -- | Atomically apply a function to the contents of an IORef and -- return the old and new values. The result of the function is forced. atomicModifyIORef'_ :: IORef a -> (a -> a) -> IO (a, a) -- | A version of atomicModifyIORef that forces the (pair) result of -- the function. atomicModifyIORefP :: IORef a -> (a -> (a, b)) -> IO b -- | Atomically replace the contents of an IORef, returning the old -- contents. atomicSwapIORef :: IORef a -> a -> IO a -- | A strict version of atomicModifyIORef. This forces both the -- value stored in the IORef and the value returned. -- -- Conceptually, -- --
--   atomicModifyIORef' ref f = do
--     -- Begin atomic block
--     old <- readIORef ref
--     let r = f old
--         new = fst r
--     writeIORef ref new
--     -- End atomic block
--     case r of
--       (!_new, !res) -> pure res
--   
-- -- The actions in the "atomic block" are not subject to interference by -- other threads. In particular, the value in the IORef cannot -- change between the readIORef and writeIORef invocations. -- -- The new value is installed in the IORef before either value is -- forced. So -- --
--   atomicModifyIORef' ref (x -> (x+1, undefined))
--   
-- -- will increment the IORef and then throw an exception in the -- calling thread. -- --
--   atomicModifyIORef' ref (x -> (undefined, x))
--   
-- -- and -- --
--   atomicModifyIORef' ref (_ -> undefined)
--   
-- -- will each raise an exception in the calling thread, but will -- also install the bottoming value in the IORef, where it -- may be read by other threads. -- -- This function imposes a memory barrier, preventing reordering around -- the "atomic block"; see Data.IORef#memmodel for details. atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b instance GHC.Classes.Eq (GHC.IORef.IORef a) -- | GHC's implementation of the ForeignPtr data type. module GHC.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 ForeignPtr :: Addr# -> ForeignPtrContents -> ForeignPtr a -- | Controls finalization of a ForeignPtr, that is, what should -- happen if the ForeignPtr becomes unreachable. Visually, these -- data constructors are appropriate in these scenarios: -- --
--                             Memory backing pointer is
--                              GC-Managed   Unmanaged
--   Finalizer functions are: +------------+-----------------+
--                   Allowed  | MallocPtr  | PlainForeignPtr |
--                            +------------+-----------------+
--                Prohibited  | PlainPtr   | FinalPtr        |
--                            +------------+-----------------+
--   
data ForeignPtrContents -- | The pointer refers to unmanaged memory that was allocated by a foreign -- function (typically using malloc). The finalizer frequently -- calls the C function free or some variant of it. PlainForeignPtr :: !IORef Finalizers -> ForeignPtrContents -- | The pointer refers to unmanaged memory that should not be freed when -- the ForeignPtr becomes unreachable. Functions that add -- finalizers to a ForeignPtr throw exceptions when the -- ForeignPtr is backed by PlainPtrMost commonly, this is -- used with Addr# literals. See Note [Why FinalPtr]. FinalPtr :: ForeignPtrContents -- | The pointer refers to a byte array. The MutableByteArray# field -- means that the MutableByteArray# is reachable (by GC) whenever -- the ForeignPtr is reachable. When the ForeignPtr becomes -- unreachable, the runtime's normal GC recovers the memory backing it. -- Here, the finalizer function intended to be used to free() -- any ancillary *unmanaged* memory pointed to by the -- MutableByteArray#. See the zlib library for an example -- of this use. -- --
    --
  1. Invariant: The Addr# in the parent ForeignPtr is an -- interior pointer into this MutableByteArray#.
  2. --
  3. Invariant: The MutableByteArray# is pinned, so the -- Addr# does not get invalidated by the GC moving the byte -- array.
  4. --
  5. Invariant: A MutableByteArray# must not be associated with -- more than one set of finalizers. For example, this is sound:
  6. --
-- --
--   incrGood :: ForeignPtr Word8 -> ForeignPtr Word8
--   incrGood (ForeignPtr p (MallocPtr m f)) = ForeignPtr (plusPtr p 1) (MallocPtr m f)
--   
-- -- But this is unsound: -- --
--   incrBad :: ForeignPtr Word8 -> IO (ForeignPtr Word8)
--   incrBad (ForeignPtr p (MallocPtr m _)) = do
--     f <- newIORef NoFinalizers
--     pure (ForeignPtr p (MallocPtr m f))
--   
MallocPtr :: MutableByteArray# RealWorld -> !IORef Finalizers -> ForeignPtrContents -- | The pointer refers to a byte array. Finalization is not supported. -- This optimizes MallocPtr by avoiding the allocation of a -- MutVar# when it is known that no one will add finalizers to -- the ForeignPtr. Functions that add finalizers to a -- ForeignPtr throw exceptions when the ForeignPtr is -- backed by PlainPtr. The invariants that apply to -- MallocPtr apply to PlainPtr as well. PlainPtr :: MutableByteArray# RealWorld -> ForeignPtrContents -- | Functions called when a ForeignPtr is finalized. Note that C -- finalizers and Haskell finalizers cannot be mixed. data Finalizers -- | No finalizer. If there is no intent to add a finalizer at any point in -- the future, consider FinalPtr or PlainPtr instead since -- these perform fewer allocations. NoFinalizers :: Finalizers -- | Finalizers are all C functions. CFinalizers :: Weak# () -> Finalizers -- | Finalizers are all Haskell functions. HaskellFinalizers :: [IO ()] -> Finalizers -- | 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 that may be -- associated with finalizers by using addForeignPtrFinalizer. newForeignPtr_ :: Ptr a -> IO (ForeignPtr a) -- | 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) -- | Allocate some memory and return a ForeignPtr to it. The memory -- will be released automatically when the ForeignPtr is -- discarded. -- -- GHC notes: mallocPlainForeignPtr has a heavily optimised -- implementation in GHC. It uses pinned memory in the garbage collected -- heap, as for mallocForeignPtr. Unlike mallocForeignPtr, a ForeignPtr -- created with mallocPlainForeignPtr carries no finalizers. It is not -- possible to add a finalizer to a ForeignPtr created with -- mallocPlainForeignPtr. This is useful for ForeignPtrs that will live -- only inside Haskell (such as those created for packed strings). -- Attempts to add a finalizer to a ForeignPtr created this way, or to -- finalize such a pointer, will throw an exception. mallocPlainForeignPtr :: 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 mallocForeignPtrBytes, except that -- the internally an optimised ForeignPtr representation with no -- finalizer is used. Attempts to add a finalizer will cause an exception -- to be thrown. mallocPlainForeignPtrBytes :: Int -> IO (ForeignPtr a) -- | This function is similar to mallocForeignPtrBytes, except that -- the size and alignment of the memory required is given explicitly as -- numbers of bytes. mallocForeignPtrAlignedBytes :: Int -> Int -> IO (ForeignPtr a) -- | This function is similar to mallocForeignPtrAlignedBytes, -- except that the internally an optimised ForeignPtr representation with -- no finalizer is used. Attempts to add a finalizer will cause an -- exception to be thrown. mallocPlainForeignPtrAlignedBytes :: Int -> Int -> IO (ForeignPtr a) -- | Turns a plain memory reference into a foreign object by associating a -- finalizer - given by the monadic operation - with the reference. -- -- When finalization is triggered by GC, 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 for GC-triggered -- finalization. -- -- When finalization is triggered by explicitly calling -- finalizeForeignPtr, the finalizer will run immediately on the -- current Haskell thread. -- -- 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. newConcForeignPtr :: Ptr a -> IO () -> 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 () -- | Like addForeignPtrFinalizer but the finalizer is passed an -- additional environment parameter. addForeignPtrFinalizerEnv :: FinalizerEnvPtr env a -> Ptr env -> ForeignPtr a -> IO () -- | 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 addForeignPtrFinalizer, where the -- finalizer is an arbitrary IO action. When finalization is -- triggered by GC, the finalizer will run in a new thread. When -- finalization is triggered by explicitly calling -- finalizeForeignPtr, the finalizer will run immediately on the -- current Haskell 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). addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO () -- | 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 -- | 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 -- | 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 -- | This is similar to withForeignPtr but comes with an important -- caveat: the user must guarantee that the continuation does not diverge -- (e.g. loop or throw an exception). In exchange for this loss of -- generality, this function offers the ability of GHC to optimise more -- aggressively. -- -- Specifically, applications of the form: unsafeWithForeignPtr fptr -- (forever something) -- -- See GHC issue #17760 for more information about the unsoundness -- behavior that this function can result in. unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b -- | This function ensures that the foreign object in question is alive at -- the given place in the sequence of IO actions. However, this comes -- with a significant caveat: the contract above does not hold if GHC can -- demonstrate that the code preceding touchForeignPtr diverges -- (e.g. by looping infinitely or throwing an exception). For this -- reason, you are strongly advised to use instead withForeignPtr -- where possible. -- -- Also, 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 () -- | Causes the finalizers associated with a foreign pointer to be run -- immediately. The foreign pointer must not be used again after this -- function is called. If the foreign pointer does not support -- finalizers, this is a no-op. finalizeForeignPtr :: ForeignPtr a -> IO () instance GHC.Classes.Eq (GHC.ForeignPtr.ForeignPtr a) instance GHC.Classes.Ord (GHC.ForeignPtr.ForeignPtr a) instance GHC.Show.Show (GHC.ForeignPtr.ForeignPtr a) -- | The ForeignPtr type and operations. This module is part of the -- Foreign Function Interface (FFI) and will usually be imported via the -- Foreign module. -- -- Unsafe API Only. module Foreign.ForeignPtr.Unsafe -- | This function extracts the pointer component of a foreign pointer. -- This is a potentially dangerous operations, as if the argument to -- unsafeForeignPtrToPtr is the last usage occurrence of the given -- foreign pointer, then its finalizer(s) will be run, which potentially -- invalidates the plain pointer just obtained. Hence, -- touchForeignPtr must be used wherever it has to be guaranteed -- that the pointer lives on - i.e., has another usage occurrence. -- -- To avoid subtle coding errors, hand written marshalling code should -- preferably use withForeignPtr rather than combinations of -- unsafeForeignPtrToPtr and touchForeignPtr. However, the -- latter routines are occasionally preferred in tool generated -- marshalling code. unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a -- | 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 addForeignPtrFinalizer but the finalizer is passed an -- additional environment parameter. 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. The foreign pointer must not be used again after this -- function is called. If the foreign pointer does not support -- finalizers, this is a no-op. 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. However, this comes -- with a significant caveat: the contract above does not hold if GHC can -- demonstrate that the code preceding touchForeignPtr diverges -- (e.g. by looping infinitely or throwing an exception). For this -- reason, you are strongly advised to use instead withForeignPtr -- where possible. -- -- Also, 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. -- -- For non-portable support of Haskell finalizers, see the -- Foreign.Concurrent 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 addForeignPtrFinalizer but the finalizer is passed an -- additional environment parameter. 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. The foreign pointer must not be used again after this -- function is called. If the foreign pointer does not support -- finalizers, this is a no-op. 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. However, this comes -- with a significant caveat: the contract above does not hold if GHC can -- demonstrate that the code preceding touchForeignPtr diverges -- (e.g. by looping infinitely or throwing an exception). For this -- reason, you are strongly advised to use instead withForeignPtr -- where possible. -- -- Also, 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. -- -- On Posix systems the I/O manager has an implicit reliance on doing a -- file read moving the file pointer. However on Windows async operations -- the kernel object representing a file does not use the file pointer -- offset. Logically this makes sense since operations can be performed -- in any arbitrary order. OVERLAPPED operations don't respect the file -- pointer offset as their intention is to support arbitrary async reads -- to anywhere at a much lower level. As such we should explicitly keep -- track of the file offsets of the target in the buffer. Any operation -- to seek should also update this entry. -- -- In order to keep us sane we try to uphold the invariant that any -- function being passed a Handle is responsible for updating the handles -- offset unless other behaviour is documented. data Buffer e Buffer :: !RawBuffer e -> BufferState -> !Int -> !Word64 -> !Int -> !Int -> Buffer e [bufRaw] :: Buffer e -> !RawBuffer e [bufState] :: Buffer e -> BufferState [bufSize] :: Buffer e -> !Int [bufOffset] :: Buffer e -> !Word64 [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 bufferAddOffset :: Int -> Buffer e -> Buffer e bufferAdjustOffset :: Word64 -> 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 bufferOffset :: Buffer e -> Word64 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 -> State# RealWorld -> (# State# RealWorld, 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 -> State# RealWorld -> (# State# RealWorld, 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 () pattern BufferCodec :: CodeBuffer from to -> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to)) -> IO () -> IO state -> (state -> IO ()) -> BufferCodec from to state -- | 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 type DecodeBuffer# = CodeBuffer# Word8 Char type EncodeBuffer# = CodeBuffer# Char Word8 type DecodingBuffer# = CodingBuffer# Word8 Char type EncodingBuffer# = CodingBuffer# Char Word8 instance GHC.Classes.Eq GHC.IO.Encoding.Types.CodingProgress instance GHC.Show.Show GHC.IO.Encoding.Types.CodingProgress instance GHC.Show.Show GHC.IO.Encoding.Types.TextEncoding -- | The IOArray type module GHC.IOArray -- | An IOArray is a mutable, boxed, non-strict array in the -- IO monad. The type arguments are as follows: -- -- newtype IOArray i e IOArray :: STArray RealWorld i e -> IOArray i e -- | Build a new IOArray newIOArray :: Ix i => (i, i) -> e -> IO (IOArray i e) -- | Read a value from an IOArray unsafeReadIOArray :: IOArray i e -> Int -> IO e -- | Write a new value into an IOArray unsafeWriteIOArray :: IOArray i e -> Int -> e -> IO () -- | Read a value from an IOArray readIOArray :: Ix i => IOArray i e -> i -> IO e -- | Write a new value into an IOArray writeIOArray :: Ix i => IOArray i e -> i -> e -> IO () boundsIOArray :: IOArray i e -> (i, i) instance GHC.Classes.Eq (GHC.IOArray.IOArray i e) -- | Type classes for I/O providers. module GHC.IO.Device -- | A low-level I/O provider where the data is bytes in memory. The Word64 -- offsets currently have no effect on POSIX system or consoles where the -- implicit behaviour of the C runtime is assumed to move the file -- pointer on every read/write without needing an explicit seek. class RawIO a -- | Read up to the specified number of bytes starting from a specified -- offset, 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 -> Word64 -> Int -> IO Int -- | Read up to the specified number of bytes starting from a specified -- offset, returning the number of bytes actually read, or Nothing -- if the end of the stream has been reached. readNonBlocking :: RawIO a => a -> Ptr Word8 -> Word64 -> Int -> IO (Maybe Int) -- | Write the specified number of bytes starting at a given offset. write :: RawIO a => a -> Ptr Word8 -> Word64 -> Int -> IO () -- | Write up to the specified number of bytes without blocking starting at -- a given offset. Returns the actual number of bytes written. writeNonBlocking :: RawIO a => a -> Ptr Word8 -> Word64 -> 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 Integer -- | 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 operation 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.Enum.Enum GHC.IO.Device.SeekMode instance GHC.Classes.Eq GHC.IO.Device.IODeviceType instance GHC.Classes.Eq GHC.IO.Device.SeekMode instance GHC.Ix.Ix GHC.IO.Device.SeekMode instance GHC.Classes.Ord GHC.IO.Device.SeekMode instance GHC.Read.Read GHC.IO.Device.SeekMode instance GHC.Show.Show GHC.IO.Device.SeekMode -- | 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) -- | Basic types for the implementation of IO Handles. module GHC.IO.Handle.Types -- | 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 FileHandle :: FilePath -> !MVar Handle__ -> Handle DuplexHandle :: FilePath -> !MVar Handle__ -> !MVar Handle__ -> Handle data Handle__ Handle__ :: !dev -> HandleType -> !IORef (Buffer Word8) -> BufferMode -> !IORef (dec_state, Buffer Word8) -> !IORef (Buffer CharBufElem) -> !IORef (BufferList CharBufElem) -> Maybe (TextEncoder enc_state) -> Maybe (TextDecoder dec_state) -> Maybe TextEncoding -> Newline -> Newline -> Maybe (MVar Handle__) -> Handle__ [haDevice] :: Handle__ -> !dev [haType] :: Handle__ -> HandleType [haByteBuffer] :: Handle__ -> !IORef (Buffer Word8) [haBufferMode] :: Handle__ -> BufferMode -- | The byte buffer just before we did our last batch of decoding. [haLastDecode] :: Handle__ -> !IORef (dec_state, Buffer Word8) [haCharBuffer] :: Handle__ -> !IORef (Buffer CharBufElem) [haBuffers] :: Handle__ -> !IORef (BufferList CharBufElem) [haEncoder] :: Handle__ -> Maybe (TextEncoder enc_state) [haDecoder] :: Handle__ -> Maybe (TextDecoder dec_state) [haCodec] :: Handle__ -> Maybe TextEncoding [haInputNL] :: Handle__ -> Newline [haOutputNL] :: Handle__ -> Newline [haOtherSide] :: Handle__ -> Maybe (MVar Handle__) showHandle :: FilePath -> String -> String checkHandleInvariants :: Handle__ -> IO () data BufferList e BufferListNil :: BufferList e BufferListCons :: RawBuffer e -> BufferList e -> BufferList e data HandleType ClosedHandle :: HandleType SemiClosedHandle :: HandleType ReadHandle :: HandleType WriteHandle :: HandleType AppendHandle :: HandleType ReadWriteHandle :: HandleType isReadableHandleType :: HandleType -> Bool isWritableHandleType :: HandleType -> Bool isReadWriteHandleType :: HandleType -> Bool isAppendHandleType :: HandleType -> 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 data BufferCodec from to state BufferCodec# :: CodeBuffer# from to -> (Buffer from -> Buffer to -> State# RealWorld -> (# State# RealWorld, 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 -> State# RealWorld -> (# State# RealWorld, 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 () pattern BufferCodec :: CodeBuffer from to -> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to)) -> IO () -> IO state -> (state -> IO ()) -> BufferCodec from to state -- | 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 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 -- | Map '\r\n' into '\n' on input, and '\n' to -- the native newline representation 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 -- | Do no newline translation at all. -- --
--   noNewlineTranslation  = NewlineMode { inputNL  = LF, outputNL = LF }
--   
noNewlineTranslation :: NewlineMode -- | Use the native newline representation on both input and output -- --
--   nativeNewlineMode  = NewlineMode { inputNL  = nativeNewline
--                                      outputNL = nativeNewline }
--   
nativeNewlineMode :: NewlineMode instance GHC.Classes.Eq GHC.IO.Handle.Types.BufferMode instance GHC.Classes.Eq GHC.IO.Handle.Types.Handle instance GHC.Classes.Eq GHC.IO.Handle.Types.Newline instance GHC.Classes.Eq GHC.IO.Handle.Types.NewlineMode instance GHC.Classes.Ord GHC.IO.Handle.Types.BufferMode instance GHC.Classes.Ord GHC.IO.Handle.Types.Newline instance GHC.Classes.Ord GHC.IO.Handle.Types.NewlineMode instance GHC.Read.Read GHC.IO.Handle.Types.BufferMode instance GHC.Read.Read GHC.IO.Handle.Types.Newline instance GHC.Read.Read GHC.IO.Handle.Types.NewlineMode instance GHC.Show.Show GHC.IO.Handle.Types.BufferMode instance GHC.Show.Show GHC.IO.Handle.Types.Handle instance GHC.Show.Show GHC.IO.Handle.Types.HandleType instance GHC.Show.Show GHC.IO.Handle.Types.Newline instance GHC.Show.Show GHC.IO.Handle.Types.NewlineMode -- | IO-related Exception types and functions module GHC.IO.Exception -- | 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 blockedIndefinitelyOnMVar :: SomeException -- | 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 blockedIndefinitelyOnSTM :: SomeException -- | There are no runnable threads, so the program is deadlocked. The -- Deadlock exception is raised in the main thread only. data Deadlock Deadlock :: Deadlock -- | This thread has exceeded its allocation limit. See -- setAllocationCounter and enableAllocationLimit. data AllocationLimitExceeded AllocationLimitExceeded :: AllocationLimitExceeded allocationLimitExceeded :: SomeException -- | assert was applied to False. newtype AssertionFailed AssertionFailed :: String -> AssertionFailed -- | 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 cannotCompactFunction :: SomeException cannotCompactPinned :: SomeException cannotCompactMutable :: SomeException -- | Superclass for asynchronous exceptions. data SomeAsyncException SomeAsyncException :: e -> SomeAsyncException asyncExceptionToException :: Exception e => e -> SomeException asyncExceptionFromException :: Exception e => SomeException -> Maybe e -- | 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 stackOverflow :: SomeException heapOverflow :: SomeException -- | 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 -- | 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 -- | The exception thrown when an infinite cycle is detected in -- fixIO. data FixIOException FixIOException :: FixIOException ioException :: IOException -> IO a -- | Raise an IOError in the IO monad. ioError :: IOError -> 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 -- | 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 IOError :: Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe FilePath -> IOException [ioe_handle] :: IOException -> Maybe Handle [ioe_type] :: IOException -> IOErrorType [ioe_location] :: IOException -> String [ioe_description] :: IOException -> String [ioe_errno] :: IOException -> Maybe CInt [ioe_filename] :: IOException -> Maybe FilePath -- | An abstract type that contains a value for each variant of -- IOError. data IOErrorType AlreadyExists :: IOErrorType NoSuchThing :: IOErrorType ResourceBusy :: IOErrorType ResourceExhausted :: IOErrorType EOF :: IOErrorType IllegalOperation :: IOErrorType PermissionDenied :: IOErrorType UserError :: IOErrorType UnsatisfiedConstraints :: IOErrorType SystemError :: IOErrorType ProtocolError :: IOErrorType OtherError :: IOErrorType InvalidArgument :: IOErrorType InappropriateType :: IOErrorType HardwareFault :: IOErrorType UnsupportedOperation :: IOErrorType TimeExpired :: IOErrorType ResourceVanished :: IOErrorType Interrupted :: IOErrorType -- | 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 assertError :: (?callStack :: CallStack) => Bool -> a -> a unsupportedOperation :: IOError untangle :: Addr# -> String -> String instance GHC.Classes.Eq GHC.IO.Exception.ArrayException instance GHC.Classes.Eq GHC.IO.Exception.AsyncException instance GHC.Classes.Eq GHC.IO.Exception.ExitCode instance GHC.Classes.Eq GHC.IO.Exception.IOErrorType instance GHC.Classes.Eq GHC.IO.Exception.IOException instance GHC.Exception.Type.Exception GHC.IO.Exception.AllocationLimitExceeded instance GHC.Exception.Type.Exception GHC.IO.Exception.ArrayException instance GHC.Exception.Type.Exception GHC.IO.Exception.AssertionFailed instance GHC.Exception.Type.Exception GHC.IO.Exception.AsyncException instance GHC.Exception.Type.Exception GHC.IO.Exception.BlockedIndefinitelyOnMVar instance GHC.Exception.Type.Exception GHC.IO.Exception.BlockedIndefinitelyOnSTM instance GHC.Exception.Type.Exception GHC.IO.Exception.CompactionFailed instance GHC.Exception.Type.Exception GHC.IO.Exception.Deadlock instance GHC.Exception.Type.Exception GHC.IO.Exception.ExitCode instance GHC.Exception.Type.Exception GHC.IO.Exception.FixIOException instance GHC.Exception.Type.Exception GHC.IO.Exception.IOException instance GHC.Exception.Type.Exception GHC.IO.Exception.SomeAsyncException instance GHC.Generics.Generic GHC.IO.Exception.ExitCode instance GHC.Classes.Ord GHC.IO.Exception.ArrayException instance GHC.Classes.Ord GHC.IO.Exception.AsyncException instance GHC.Classes.Ord GHC.IO.Exception.ExitCode instance GHC.Read.Read GHC.IO.Exception.ExitCode instance GHC.Show.Show GHC.IO.Exception.AllocationLimitExceeded instance GHC.Show.Show GHC.IO.Exception.ArrayException instance GHC.Show.Show GHC.IO.Exception.AssertionFailed instance GHC.Show.Show GHC.IO.Exception.AsyncException instance GHC.Show.Show GHC.IO.Exception.BlockedIndefinitelyOnMVar instance GHC.Show.Show GHC.IO.Exception.BlockedIndefinitelyOnSTM instance GHC.Show.Show GHC.IO.Exception.CompactionFailed instance GHC.Show.Show GHC.IO.Exception.Deadlock instance GHC.Show.Show GHC.IO.Exception.ExitCode instance GHC.Show.Show GHC.IO.Exception.FixIOException instance GHC.Show.Show GHC.IO.Exception.IOErrorType instance GHC.Show.Show GHC.IO.Exception.IOException instance GHC.Show.Show GHC.IO.Exception.SomeAsyncException -- | 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) recoverDecode# :: CodingFailureMode -> Buffer Word8 -> Buffer Char -> State# RealWorld -> (# State# RealWorld, Buffer Word8, Buffer Char #) recoverEncode# :: CodingFailureMode -> Buffer Char -> Buffer Word8 -> State# RealWorld -> (# State# RealWorld, Buffer Char, Buffer Word8 #) instance GHC.Show.Show GHC.IO.Encoding.Failure.CodingFailureMode -- | UTF-8 Codec for the IO library -- -- This is one of several UTF-8 implementations provided by GHC; see Note -- [GHC's many UTF-8 implementations] in GHC.Encoding.UTF8 for an -- overview. -- -- 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. -- -- The underlying implementation is wrapping the stdlib.h -- malloc, realloc, and free. In other words -- it should be safe to allocate using C-malloc, and free memory -- with free from this module. 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 size align f executes the -- computation f, passing as argument a pointer to a temporarily -- allocated block of memory of size bytes and aligned to -- align bytes. The value of align must be a power of -- two. -- -- 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. 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) -- | Like 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 :: forall a b. 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 -- | 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 :: 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. -- -- Note that this does not NUL terminate the resulting string. -- -- newCStringLen :: TextEncoding -> String -> IO CStringLen -- | Marshal a Haskell string into a NUL-terminated C string (ie, character -- array) with explicit length information. -- -- newCStringLen0 :: 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. -- -- Note that this does not NUL terminate the resulting string. -- -- withCStringLen :: TextEncoding -> String -> (CStringLen -> IO a) -> IO a -- | Marshal a Haskell string into a NUL-terminated C string (ie, character -- array) in temporary storage, with explicit length information. -- -- withCStringLen0 :: 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 -- | Common Timer definitions shared between WinIO and RIO. module GHC.Event.TimeOut -- | A priority search queue, with timeouts as priorities. type TimeoutQueue = PSQ TimeoutCallback -- | Warning: since the TimeoutCallback is called from the I/O -- manager, it must not throw an exception or block for a long period of -- time. In particular, be wary of throwTo and killThread: -- if the target thread is making a foreign call, these functions will -- block until the call completes. type TimeoutCallback = IO () -- | An edit to apply to a TimeoutQueue. type TimeoutEdit = TimeoutQueue -> TimeoutQueue -- | A timeout registration cookie. newtype TimeoutKey TK :: Unique -> TimeoutKey instance GHC.Classes.Eq GHC.Event.TimeOut.TimeoutKey instance GHC.Classes.Ord GHC.Event.TimeOut.TimeoutKey -- | Simple UTF-8 codecs supporting non-streaming encoding/decoding. For -- encoding where codepoints may be broken across buffers, see -- GHC.IO.Encoding.UTF8. -- -- This is one of several UTF-8 implementations provided by GHC; see Note -- [GHC's many UTF-8 implementations] in GHC.Encoding.UTF8 for an -- overview. module GHC.Encoding.UTF8 -- | Decode a single character at the given Addr#. utf8DecodeCharAddr# :: Addr# -> Int# -> (# Char#, Int# #) -- | Decode a single codepoint starting at the given Ptr. utf8DecodeCharPtr :: Ptr Word8 -> (Char, Int) -- | Decode a single codepoint starting at the given byte offset into a -- ByteArray#. utf8DecodeCharByteArray# :: ByteArray# -> Int# -> (# Char#, Int# #) utf8DecodeByteArray# :: ByteArray# -> [Char] utf8DecodeForeignPtr :: ForeignPtr Word8 -> Int -> Int -> [Char] utf8CountCharsByteArray# :: ByteArray# -> Int utf8CompareByteArray# :: ByteArray# -> ByteArray# -> Ordering utf8EncodePtr :: Ptr Word8 -> String -> IO () utf8EncodeByteArray# :: String -> ByteArray# utf8EncodedLength :: String -> Int module GHC.Weak.Finalize -- | Set the global action called to report exceptions thrown by weak -- pointer finalizers to the user. setFinalizerExceptionHandler :: (SomeException -> IO ()) -> IO () -- | Get the global action called to report exceptions thrown by weak -- pointer finalizers to the user. getFinalizerExceptionHandler :: IO (SomeException -> IO ()) -- | An exception handler for Handle finalization that prints the -- error to the given Handle, but doesn't rethrow it. printToHandleFinalizerExceptionHandler :: Handle -> SomeException -> IO () -- | Run a batch of finalizers from the garbage collector. We're given an -- array of finalizers and the length of the array, and we just call each -- one in turn. runFinalizerBatch :: Int -> Array# (State# RealWorld -> State# RealWorld) -> IO () -- | Weak pointers. module GHC.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 resurrect 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, MVar, -- and TVar. However, to place a finalizer on one of these -- types, you should use the specific operation provided for that type, -- e.g. mkWeakIORef, mkWeakMVar and mkWeakTVar -- respectively. 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 Weak :: Weak# v -> 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 () -- | Set the global action called to report exceptions thrown by weak -- pointer finalizers to the user. setFinalizerExceptionHandler :: (SomeException -> IO ()) -> IO () -- | Get the global action called to report exceptions thrown by weak -- pointer finalizers to the user. getFinalizerExceptionHandler :: IO (SomeException -> IO ()) -- | An exception handler for Handle finalization that prints the -- error to the given Handle, but doesn't rethrow it. printToHandleFinalizerExceptionHandler :: Handle -> SomeException -> IO () -- | Mutable references in the IO monad. module Data.IORef -- | A mutable variable in the IO monad. -- --
--   >>> import Data.IORef
--   
--   >>> r <- newIORef 0
--   
--   >>> readIORef r
--   0
--   
--   >>> writeIORef r 1
--   
--   >>> readIORef r
--   1
--   
--   >>> atomicWriteIORef r 2
--   
--   >>> readIORef r
--   2
--   
--   >>> modifyIORef' r (+ 1)
--   
--   >>> readIORef r
--   3
--   
--   >>> atomicModifyIORef' r (\a -> (a + 1, ()))
--   
--   >>> readIORef r
--   4
--   
-- -- See also STRef and MVar. data IORef a -- | Build a new IORef newIORef :: a -> IO (IORef a) -- | Read the value of an IORef. -- -- Beware that the CPU executing a thread can reorder reads or writes to -- independent locations. See Data.IORef#memmodel for more -- details. readIORef :: IORef a -> IO a -- | Write a new value into an IORef. -- -- This function does not create a memory barrier and can be reordered -- with other independent reads and writes within a thread, which may -- cause issues for multithreaded execution. In these cases, consider -- using atomicWriteIORef instead. See Data.IORef#memmodel -- for more details. writeIORef :: IORef a -> a -> IO () -- | Mutate the contents of an IORef, combining readIORef and -- writeIORef. This is not an atomic update, consider using -- atomicModifyIORef when operating in a multithreaded -- environment. -- -- Be warned that modifyIORef does not apply the function -- strictly. This means if the program calls modifyIORef many -- times, but seldom uses the value, thunks will pile up in memory -- resulting in a space leak. This is a common mistake made when using an -- IORef as a counter. For example, the following will likely produce a -- stack overflow: -- --
--   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. This is not an atomic update, -- consider using atomicModifyIORef' when operating in a -- multithreaded environment. 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. -- -- Conceptually, -- --
--   atomicModifyIORef ref f = do
--     -- Begin atomic block
--     old <- readIORef ref
--     let r = f old
--         new = fst r
--     writeIORef ref new
--     -- End atomic block
--     case r of
--       (_new, res) -> pure res
--   
-- -- The actions in the section labeled "atomic block" are not subject to -- interference from other threads. In particular, it is impossible for -- the value in the IORef to change between the readIORef -- and writeIORef invocations. -- -- The user-supplied function is applied to the value stored in the -- IORef, yielding a new value to store in the IORef and a -- value to return. After the new value is (lazily) stored in the -- IORef, atomicModifyIORef forces the result pair, but -- does not force either component of the result. To force both -- components, use atomicModifyIORef'. -- -- Note that -- --
--   atomicModifyIORef ref (_ -> undefined)
--   
-- -- will raise an exception in the calling thread, but will also -- install the bottoming value in the IORef, where it may be read -- by other threads. -- -- This function imposes a memory barrier, preventing reordering around -- the "atomic block"; see Data.IORef#memmodel for details. atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b -- | A strict version of atomicModifyIORef. This forces both the -- value stored in the IORef and the value returned. -- -- Conceptually, -- --
--   atomicModifyIORef' ref f = do
--     -- Begin atomic block
--     old <- readIORef ref
--     let r = f old
--         new = fst r
--     writeIORef ref new
--     -- End atomic block
--     case r of
--       (!_new, !res) -> pure res
--   
-- -- The actions in the "atomic block" are not subject to interference by -- other threads. In particular, the value in the IORef cannot -- change between the readIORef and writeIORef invocations. -- -- The new value is installed in the IORef before either value is -- forced. So -- --
--   atomicModifyIORef' ref (x -> (x+1, undefined))
--   
-- -- will increment the IORef and then throw an exception in the -- calling thread. -- --
--   atomicModifyIORef' ref (x -> (undefined, x))
--   
-- -- and -- --
--   atomicModifyIORef' ref (_ -> undefined)
--   
-- -- will each raise an exception in the calling thread, but will -- also install the bottoming value in the IORef, where it -- may be read by other threads. -- -- This function imposes a memory barrier, preventing reordering around -- the "atomic block"; see Data.IORef#memmodel for details. atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b -- | Variant of writeIORef. The prefix "atomic" relates to a fact -- that it imposes a reordering barrier, similar to -- atomicModifyIORef. Such a write will not be reordered with -- other reads or writes even on CPUs with weak memory model. 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)) -- | 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. -- -- When finalization is triggered by GC, 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 for GC-triggered -- finalization. -- -- When finalization is triggered by explicitly calling -- finalizeForeignPtr, the finalizer will run immediately on the -- current Haskell thread. -- -- 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 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. -- -- On GHC, the runtime will ensure that any Haskell thread will only see -- "its own" errno, by saving and restoring the value when -- Haskell threads are scheduled across OS threads. 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. -- Note that the previously allocated space is still retained in the same -- Pool and will only be freed when the entire Pool is -- freed. 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 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 CBlkSize CBlkSize :: Int64 -> CBlkSize newtype CBlkCnt CBlkCnt :: Int64 -> CBlkCnt newtype CClockId CClockId :: Int32 -> CClockId newtype CFsBlkCnt CFsBlkCnt :: Word64 -> CFsBlkCnt newtype CFsFilCnt CFsFilCnt :: Word64 -> CFsFilCnt newtype CId CId :: Word32 -> CId newtype CKey CKey :: Int32 -> CKey newtype CTimer CTimer :: CUIntPtr -> CTimer newtype CSocklen CSocklen :: Word32 -> CSocklen newtype CNfds CNfds :: Word64 -> CNfds 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.Bits.Bits System.Posix.Types.CBlkCnt instance GHC.Bits.Bits System.Posix.Types.CBlkSize instance GHC.Bits.Bits System.Posix.Types.CClockId instance GHC.Bits.Bits System.Posix.Types.CDev instance GHC.Bits.Bits System.Posix.Types.CFsBlkCnt instance GHC.Bits.Bits System.Posix.Types.CFsFilCnt instance GHC.Bits.Bits System.Posix.Types.CGid instance GHC.Bits.Bits System.Posix.Types.CId instance GHC.Bits.Bits System.Posix.Types.CIno instance GHC.Bits.Bits System.Posix.Types.CKey instance GHC.Bits.Bits System.Posix.Types.CMode instance GHC.Bits.Bits System.Posix.Types.CNfds instance GHC.Bits.Bits System.Posix.Types.CNlink instance GHC.Bits.Bits System.Posix.Types.COff instance GHC.Bits.Bits System.Posix.Types.CPid instance GHC.Bits.Bits System.Posix.Types.CRLim instance GHC.Bits.Bits System.Posix.Types.CSocklen instance GHC.Bits.Bits System.Posix.Types.CSsize instance GHC.Bits.Bits System.Posix.Types.CTcflag instance GHC.Bits.Bits System.Posix.Types.CUid instance GHC.Bits.Bits System.Posix.Types.Fd instance GHC.Enum.Bounded System.Posix.Types.CBlkCnt instance GHC.Enum.Bounded System.Posix.Types.CBlkSize instance GHC.Enum.Bounded System.Posix.Types.CClockId instance GHC.Enum.Bounded System.Posix.Types.CDev instance GHC.Enum.Bounded System.Posix.Types.CFsBlkCnt instance GHC.Enum.Bounded System.Posix.Types.CFsFilCnt instance GHC.Enum.Bounded System.Posix.Types.CGid instance GHC.Enum.Bounded System.Posix.Types.CId instance GHC.Enum.Bounded System.Posix.Types.CIno instance GHC.Enum.Bounded System.Posix.Types.CKey instance GHC.Enum.Bounded System.Posix.Types.CMode instance GHC.Enum.Bounded System.Posix.Types.CNfds instance GHC.Enum.Bounded System.Posix.Types.CNlink instance GHC.Enum.Bounded System.Posix.Types.COff instance GHC.Enum.Bounded System.Posix.Types.CPid instance GHC.Enum.Bounded System.Posix.Types.CRLim instance GHC.Enum.Bounded System.Posix.Types.CSocklen instance GHC.Enum.Bounded System.Posix.Types.CSsize instance GHC.Enum.Bounded System.Posix.Types.CTcflag instance GHC.Enum.Bounded System.Posix.Types.CUid instance GHC.Enum.Bounded System.Posix.Types.Fd instance GHC.Enum.Enum System.Posix.Types.CBlkCnt instance GHC.Enum.Enum System.Posix.Types.CBlkSize instance GHC.Enum.Enum System.Posix.Types.CCc instance GHC.Enum.Enum System.Posix.Types.CClockId instance GHC.Enum.Enum System.Posix.Types.CDev instance GHC.Enum.Enum System.Posix.Types.CFsBlkCnt instance GHC.Enum.Enum System.Posix.Types.CFsFilCnt instance GHC.Enum.Enum System.Posix.Types.CGid instance GHC.Enum.Enum System.Posix.Types.CId instance GHC.Enum.Enum System.Posix.Types.CIno instance GHC.Enum.Enum System.Posix.Types.CKey instance GHC.Enum.Enum System.Posix.Types.CMode instance GHC.Enum.Enum System.Posix.Types.CNfds instance GHC.Enum.Enum System.Posix.Types.CNlink instance GHC.Enum.Enum System.Posix.Types.COff instance GHC.Enum.Enum System.Posix.Types.CPid instance GHC.Enum.Enum System.Posix.Types.CRLim instance GHC.Enum.Enum System.Posix.Types.CSocklen instance GHC.Enum.Enum System.Posix.Types.CSpeed instance GHC.Enum.Enum System.Posix.Types.CSsize instance GHC.Enum.Enum System.Posix.Types.CTcflag instance GHC.Enum.Enum System.Posix.Types.CUid instance GHC.Enum.Enum System.Posix.Types.Fd instance GHC.Classes.Eq System.Posix.Types.CBlkCnt instance GHC.Classes.Eq System.Posix.Types.CBlkSize instance GHC.Classes.Eq System.Posix.Types.CCc instance GHC.Classes.Eq System.Posix.Types.CClockId instance GHC.Classes.Eq System.Posix.Types.CDev instance GHC.Classes.Eq System.Posix.Types.CFsBlkCnt instance GHC.Classes.Eq System.Posix.Types.CFsFilCnt instance GHC.Classes.Eq System.Posix.Types.CGid instance GHC.Classes.Eq System.Posix.Types.CId instance GHC.Classes.Eq System.Posix.Types.CIno instance GHC.Classes.Eq System.Posix.Types.CKey instance GHC.Classes.Eq System.Posix.Types.CMode instance GHC.Classes.Eq System.Posix.Types.CNfds instance GHC.Classes.Eq System.Posix.Types.CNlink instance GHC.Classes.Eq System.Posix.Types.COff instance GHC.Classes.Eq System.Posix.Types.CPid instance GHC.Classes.Eq System.Posix.Types.CRLim instance GHC.Classes.Eq System.Posix.Types.CSocklen instance GHC.Classes.Eq System.Posix.Types.CSpeed instance GHC.Classes.Eq System.Posix.Types.CSsize instance GHC.Classes.Eq System.Posix.Types.CTcflag instance GHC.Classes.Eq System.Posix.Types.CTimer instance GHC.Classes.Eq System.Posix.Types.CUid instance GHC.Classes.Eq System.Posix.Types.Fd instance GHC.Bits.FiniteBits System.Posix.Types.CBlkCnt instance GHC.Bits.FiniteBits System.Posix.Types.CBlkSize instance GHC.Bits.FiniteBits System.Posix.Types.CClockId instance GHC.Bits.FiniteBits System.Posix.Types.CDev instance GHC.Bits.FiniteBits System.Posix.Types.CFsBlkCnt instance GHC.Bits.FiniteBits System.Posix.Types.CFsFilCnt instance GHC.Bits.FiniteBits System.Posix.Types.CGid instance GHC.Bits.FiniteBits System.Posix.Types.CId instance GHC.Bits.FiniteBits System.Posix.Types.CIno instance GHC.Bits.FiniteBits System.Posix.Types.CKey instance GHC.Bits.FiniteBits System.Posix.Types.CMode instance GHC.Bits.FiniteBits System.Posix.Types.CNfds instance GHC.Bits.FiniteBits System.Posix.Types.CNlink instance GHC.Bits.FiniteBits System.Posix.Types.COff instance GHC.Bits.FiniteBits System.Posix.Types.CPid instance GHC.Bits.FiniteBits System.Posix.Types.CRLim instance GHC.Bits.FiniteBits System.Posix.Types.CSocklen instance GHC.Bits.FiniteBits System.Posix.Types.CSsize instance GHC.Bits.FiniteBits System.Posix.Types.CTcflag instance GHC.Bits.FiniteBits System.Posix.Types.CUid instance GHC.Bits.FiniteBits System.Posix.Types.Fd instance GHC.Real.Integral System.Posix.Types.CBlkCnt instance GHC.Real.Integral System.Posix.Types.CBlkSize instance GHC.Real.Integral System.Posix.Types.CClockId instance GHC.Real.Integral System.Posix.Types.CDev instance GHC.Real.Integral System.Posix.Types.CFsBlkCnt instance GHC.Real.Integral System.Posix.Types.CFsFilCnt instance GHC.Real.Integral System.Posix.Types.CGid instance GHC.Real.Integral System.Posix.Types.CId instance GHC.Real.Integral System.Posix.Types.CIno instance GHC.Real.Integral System.Posix.Types.CKey instance GHC.Real.Integral System.Posix.Types.CMode instance GHC.Real.Integral System.Posix.Types.CNfds instance GHC.Real.Integral System.Posix.Types.CNlink instance GHC.Real.Integral System.Posix.Types.COff instance GHC.Real.Integral System.Posix.Types.CPid instance GHC.Real.Integral System.Posix.Types.CRLim instance GHC.Real.Integral System.Posix.Types.CSocklen instance GHC.Real.Integral System.Posix.Types.CSsize instance GHC.Real.Integral System.Posix.Types.CTcflag instance GHC.Real.Integral System.Posix.Types.CUid instance GHC.Real.Integral System.Posix.Types.Fd instance GHC.Ix.Ix System.Posix.Types.CBlkCnt instance GHC.Ix.Ix System.Posix.Types.CBlkSize instance GHC.Ix.Ix System.Posix.Types.CClockId instance GHC.Ix.Ix System.Posix.Types.CDev instance GHC.Ix.Ix System.Posix.Types.CFsBlkCnt instance GHC.Ix.Ix System.Posix.Types.CFsFilCnt instance GHC.Ix.Ix System.Posix.Types.CGid instance GHC.Ix.Ix System.Posix.Types.CId instance GHC.Ix.Ix System.Posix.Types.CIno instance GHC.Ix.Ix System.Posix.Types.CKey instance GHC.Ix.Ix System.Posix.Types.CMode instance GHC.Ix.Ix System.Posix.Types.CNfds instance GHC.Ix.Ix System.Posix.Types.CNlink instance GHC.Ix.Ix System.Posix.Types.COff instance GHC.Ix.Ix System.Posix.Types.CPid instance GHC.Ix.Ix System.Posix.Types.CRLim instance GHC.Ix.Ix System.Posix.Types.CSocklen instance GHC.Ix.Ix System.Posix.Types.CSsize instance GHC.Ix.Ix System.Posix.Types.CTcflag instance GHC.Ix.Ix System.Posix.Types.CUid instance GHC.Ix.Ix System.Posix.Types.Fd instance GHC.Num.Num System.Posix.Types.CBlkCnt instance GHC.Num.Num System.Posix.Types.CBlkSize instance GHC.Num.Num System.Posix.Types.CCc instance GHC.Num.Num System.Posix.Types.CClockId instance GHC.Num.Num System.Posix.Types.CDev instance GHC.Num.Num System.Posix.Types.CFsBlkCnt instance GHC.Num.Num System.Posix.Types.CFsFilCnt instance GHC.Num.Num System.Posix.Types.CGid instance GHC.Num.Num System.Posix.Types.CId instance GHC.Num.Num System.Posix.Types.CIno instance GHC.Num.Num System.Posix.Types.CKey instance GHC.Num.Num System.Posix.Types.CMode instance GHC.Num.Num System.Posix.Types.CNfds instance GHC.Num.Num System.Posix.Types.CNlink instance GHC.Num.Num System.Posix.Types.COff instance GHC.Num.Num System.Posix.Types.CPid instance GHC.Num.Num System.Posix.Types.CRLim instance GHC.Num.Num System.Posix.Types.CSocklen instance GHC.Num.Num System.Posix.Types.CSpeed instance GHC.Num.Num System.Posix.Types.CSsize instance GHC.Num.Num System.Posix.Types.CTcflag instance GHC.Num.Num System.Posix.Types.CUid instance GHC.Num.Num System.Posix.Types.Fd instance GHC.Classes.Ord System.Posix.Types.CBlkCnt instance GHC.Classes.Ord System.Posix.Types.CBlkSize instance GHC.Classes.Ord System.Posix.Types.CCc instance GHC.Classes.Ord System.Posix.Types.CClockId instance GHC.Classes.Ord System.Posix.Types.CDev instance GHC.Classes.Ord System.Posix.Types.CFsBlkCnt instance GHC.Classes.Ord System.Posix.Types.CFsFilCnt instance GHC.Classes.Ord System.Posix.Types.CGid instance GHC.Classes.Ord System.Posix.Types.CId instance GHC.Classes.Ord System.Posix.Types.CIno instance GHC.Classes.Ord System.Posix.Types.CKey instance GHC.Classes.Ord System.Posix.Types.CMode instance GHC.Classes.Ord System.Posix.Types.CNfds instance GHC.Classes.Ord System.Posix.Types.CNlink instance GHC.Classes.Ord System.Posix.Types.COff instance GHC.Classes.Ord System.Posix.Types.CPid instance GHC.Classes.Ord System.Posix.Types.CRLim instance GHC.Classes.Ord System.Posix.Types.CSocklen instance GHC.Classes.Ord System.Posix.Types.CSpeed instance GHC.Classes.Ord System.Posix.Types.CSsize instance GHC.Classes.Ord System.Posix.Types.CTcflag instance GHC.Classes.Ord System.Posix.Types.CTimer instance GHC.Classes.Ord System.Posix.Types.CUid instance GHC.Classes.Ord System.Posix.Types.Fd instance GHC.Read.Read System.Posix.Types.CBlkCnt instance GHC.Read.Read System.Posix.Types.CBlkSize instance GHC.Read.Read System.Posix.Types.CCc instance GHC.Read.Read System.Posix.Types.CClockId instance GHC.Read.Read System.Posix.Types.CDev instance GHC.Read.Read System.Posix.Types.CFsBlkCnt instance GHC.Read.Read System.Posix.Types.CFsFilCnt instance GHC.Read.Read System.Posix.Types.CGid instance GHC.Read.Read System.Posix.Types.CId instance GHC.Read.Read System.Posix.Types.CIno instance GHC.Read.Read System.Posix.Types.CKey instance GHC.Read.Read System.Posix.Types.CMode instance GHC.Read.Read System.Posix.Types.CNfds instance GHC.Read.Read System.Posix.Types.CNlink instance GHC.Read.Read System.Posix.Types.COff instance GHC.Read.Read System.Posix.Types.CPid instance GHC.Read.Read System.Posix.Types.CRLim instance GHC.Read.Read System.Posix.Types.CSocklen instance GHC.Read.Read System.Posix.Types.CSpeed instance GHC.Read.Read System.Posix.Types.CSsize instance GHC.Read.Read System.Posix.Types.CTcflag instance GHC.Read.Read System.Posix.Types.CUid instance GHC.Read.Read System.Posix.Types.Fd instance GHC.Real.Real System.Posix.Types.CBlkCnt instance GHC.Real.Real System.Posix.Types.CBlkSize instance GHC.Real.Real System.Posix.Types.CCc instance GHC.Real.Real System.Posix.Types.CClockId instance GHC.Real.Real System.Posix.Types.CDev instance GHC.Real.Real System.Posix.Types.CFsBlkCnt instance GHC.Real.Real System.Posix.Types.CFsFilCnt instance GHC.Real.Real System.Posix.Types.CGid instance GHC.Real.Real System.Posix.Types.CId instance GHC.Real.Real System.Posix.Types.CIno instance GHC.Real.Real System.Posix.Types.CKey instance GHC.Real.Real System.Posix.Types.CMode instance GHC.Real.Real System.Posix.Types.CNfds instance GHC.Real.Real System.Posix.Types.CNlink instance GHC.Real.Real System.Posix.Types.COff instance GHC.Real.Real System.Posix.Types.CPid instance GHC.Real.Real System.Posix.Types.CRLim instance GHC.Real.Real System.Posix.Types.CSocklen instance GHC.Real.Real System.Posix.Types.CSpeed instance GHC.Real.Real System.Posix.Types.CSsize instance GHC.Real.Real System.Posix.Types.CTcflag instance GHC.Real.Real System.Posix.Types.CUid instance GHC.Real.Real System.Posix.Types.Fd instance GHC.Show.Show System.Posix.Types.CBlkCnt instance GHC.Show.Show System.Posix.Types.CBlkSize instance GHC.Show.Show System.Posix.Types.CCc instance GHC.Show.Show System.Posix.Types.CClockId instance GHC.Show.Show System.Posix.Types.CDev instance GHC.Show.Show System.Posix.Types.CFsBlkCnt instance GHC.Show.Show System.Posix.Types.CFsFilCnt instance GHC.Show.Show System.Posix.Types.CGid instance GHC.Show.Show System.Posix.Types.CId instance GHC.Show.Show System.Posix.Types.CIno instance GHC.Show.Show System.Posix.Types.CKey instance GHC.Show.Show System.Posix.Types.CMode instance GHC.Show.Show System.Posix.Types.CNfds instance GHC.Show.Show System.Posix.Types.CNlink instance GHC.Show.Show System.Posix.Types.COff instance GHC.Show.Show System.Posix.Types.CPid instance GHC.Show.Show System.Posix.Types.CRLim instance GHC.Show.Show System.Posix.Types.CSocklen instance GHC.Show.Show System.Posix.Types.CSpeed instance GHC.Show.Show System.Posix.Types.CSsize instance GHC.Show.Show System.Posix.Types.CTcflag instance GHC.Show.Show System.Posix.Types.CTimer instance GHC.Show.Show System.Posix.Types.CUid instance GHC.Show.Show System.Posix.Types.Fd instance Foreign.Storable.Storable System.Posix.Types.CBlkCnt instance Foreign.Storable.Storable System.Posix.Types.CBlkSize instance Foreign.Storable.Storable System.Posix.Types.CCc instance Foreign.Storable.Storable System.Posix.Types.CClockId instance Foreign.Storable.Storable System.Posix.Types.CDev instance Foreign.Storable.Storable System.Posix.Types.CFsBlkCnt instance Foreign.Storable.Storable System.Posix.Types.CFsFilCnt instance Foreign.Storable.Storable System.Posix.Types.CGid instance Foreign.Storable.Storable System.Posix.Types.CId instance Foreign.Storable.Storable System.Posix.Types.CIno instance Foreign.Storable.Storable System.Posix.Types.CKey instance Foreign.Storable.Storable System.Posix.Types.CMode instance Foreign.Storable.Storable System.Posix.Types.CNfds instance Foreign.Storable.Storable System.Posix.Types.CNlink instance Foreign.Storable.Storable System.Posix.Types.COff instance Foreign.Storable.Storable System.Posix.Types.CPid instance Foreign.Storable.Storable System.Posix.Types.CRLim instance Foreign.Storable.Storable System.Posix.Types.CSocklen instance Foreign.Storable.Storable System.Posix.Types.CSpeed instance Foreign.Storable.Storable System.Posix.Types.CSsize instance Foreign.Storable.Storable System.Posix.Types.CTcflag instance Foreign.Storable.Storable System.Posix.Types.CTimer instance Foreign.Storable.Storable System.Posix.Types.CUid instance Foreign.Storable.Storable System.Posix.Types.Fd -- | POSIX support layer for the standard libraries. This library is built -- on *every* platform, including Win32. -- -- Non-posix compliant in order to support the following features: * -- S_ISSOCK (no sockets in POSIX) module System.Posix.Internals puts :: String -> IO () data CFLock data CGroup data CLconv data CPasswd data CSigaction data CSigset data CStat data CTermios data CTm data CTms data CUtimbuf data CUtsname type FD = CInt fdFileSize :: FD -> IO Integer fileType :: FilePath -> IO IODeviceType fdStat :: FD -> IO (IODeviceType, CDev, CIno) fdType :: FD -> IO IODeviceType statGetType :: Ptr CStat -> IO IODeviceType ioe_unknownfiletype :: IOException fdGetMode :: FD -> IO IOMode withFilePath :: FilePath -> (CString -> IO a) -> IO a newFilePath :: FilePath -> IO CString peekFilePath :: CString -> IO FilePath peekFilePathLen :: CStringLen -> IO FilePath -- | Check an encoded FilePath for internal NUL octets as these are -- disallowed in POSIX filepaths. See #13660. checkForInteriorNuls :: FilePath -> CStringLen -> IO () throwInternalNulError :: FilePath -> IO a setEcho :: FD -> Bool -> IO () getEcho :: FD -> IO Bool setCooked :: FD -> Bool -> IO () tcSetAttr :: FD -> (Ptr CTermios -> IO a) -> IO a get_saved_termios :: CInt -> IO (Ptr CTermios) set_saved_termios :: CInt -> Ptr CTermios -> IO () setNonBlockingFD :: FD -> Bool -> IO () setCloseOnExec :: FD -> IO () type CFilePath = CString -- | The same as c_safe_open, but an interruptible operation -- as described in Control.Exception—it respects -- uninterruptibleMask but not mask. -- -- We want to be able to interrupt an openFile call if it's expensive -- (NFS, FUSE, etc.), and we especially need to be able to interrupt a -- blocking open call. See #17912. c_interruptible_open :: CFilePath -> CInt -> CMode -> IO CInt c_safe_open :: CFilePath -> CInt -> CMode -> IO CInt -- | Consult the RTS to find whether it is threaded. hostIsThreaded :: Bool c_open :: CFilePath -> CInt -> CMode -> IO CInt c_interruptible_open_ :: CFilePath -> CInt -> CMode -> IO CInt rtsIsThreaded_ :: Int c_safe_open_ :: CFilePath -> CInt -> CMode -> IO CInt c_fstat :: CInt -> Ptr CStat -> IO CInt lstat :: CFilePath -> Ptr CStat -> IO CInt c_read :: CInt -> Ptr Word8 -> CSize -> IO CSsize c_safe_read :: CInt -> Ptr Word8 -> CSize -> IO CSsize c_umask :: CMode -> IO CMode c_write :: CInt -> Ptr Word8 -> CSize -> IO CSsize c_safe_write :: CInt -> Ptr Word8 -> CSize -> IO CSsize c_pipe :: Ptr CInt -> IO CInt c_lseek :: CInt -> COff -> CInt -> IO COff c_access :: CString -> CInt -> IO CInt c_chmod :: CString -> CMode -> IO CInt c_close :: CInt -> IO CInt c_creat :: CString -> CMode -> IO CInt c_dup :: CInt -> IO CInt c_dup2 :: CInt -> CInt -> IO CInt c_isatty :: CInt -> IO CInt c_unlink :: CString -> IO CInt c_utime :: CString -> Ptr CUtimbuf -> IO CInt c_getpid :: IO CPid c_stat :: CFilePath -> Ptr CStat -> IO CInt c_ftruncate :: CInt -> COff -> IO CInt c_fcntl_read :: CInt -> CInt -> IO CInt c_fcntl_write :: CInt -> CInt -> CLong -> IO CInt c_fcntl_lock :: CInt -> CInt -> Ptr CFLock -> IO CInt c_fork :: IO CPid c_link :: CString -> CString -> IO CInt c_mkfifo :: CString -> CMode -> IO CInt c_sigemptyset :: Ptr CSigset -> IO CInt c_sigaddset :: Ptr CSigset -> CInt -> IO CInt c_sigprocmask :: CInt -> Ptr CSigset -> Ptr CSigset -> IO CInt c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid o_RDONLY :: CInt o_WRONLY :: CInt o_RDWR :: CInt o_APPEND :: CInt o_CREAT :: CInt o_EXCL :: CInt o_TRUNC :: CInt o_NOCTTY :: CInt o_NONBLOCK :: CInt o_BINARY :: CInt c_s_isreg :: CMode -> CInt c_s_ischr :: CMode -> CInt c_s_isblk :: CMode -> CInt c_s_isdir :: CMode -> CInt c_s_isfifo :: CMode -> CInt s_isreg :: CMode -> Bool s_ischr :: CMode -> Bool s_isblk :: CMode -> Bool s_isdir :: CMode -> Bool s_isfifo :: CMode -> Bool sizeof_stat :: Int st_mtime :: Ptr CStat -> IO CTime st_size :: Ptr CStat -> IO COff st_mode :: Ptr CStat -> IO CMode st_dev :: Ptr CStat -> IO CDev st_ino :: Ptr CStat -> IO CIno const_echo :: CInt const_tcsanow :: CInt const_icanon :: CInt const_vmin :: CInt const_vtime :: CInt const_sigttou :: CInt const_sig_block :: CInt const_sig_setmask :: CInt const_f_getfl :: CInt const_f_setfl :: CInt const_f_setfd :: CInt const_fd_cloexec :: CLong sizeof_termios :: Int sizeof_sigset_t :: Int c_lflag :: Ptr CTermios -> IO CTcflag poke_c_lflag :: Ptr CTermios -> CTcflag -> IO () ptr_c_cc :: Ptr CTermios -> IO (Ptr Word8) s_issock :: CMode -> Bool c_s_issock :: CMode -> CInt dEFAULT_BUFFER_SIZE :: Int sEEK_CUR :: CInt sEEK_SET :: CInt sEEK_END :: CInt -- | 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 -- | RtsTime 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 -> 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 [returnDecayFactor] :: 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 -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Word -> IoSubSystem -> Word32 -> MiscFlags [tickInterval] :: MiscFlags -> RtsTime [installSignalHandlers] :: MiscFlags -> Bool [installSEHHandlers] :: MiscFlags -> Bool [generateCrashDumpFile] :: MiscFlags -> Bool [generateStackTrace] :: MiscFlags -> Bool [machineReadable] :: MiscFlags -> Bool [disableDelayedOsMemoryReturn] :: MiscFlags -> Bool [internalCounters] :: MiscFlags -> Bool [linkerAlwaysPic] :: MiscFlags -> Bool -- | address to ask the OS for memory for the linker, 0 ==> off [linkerMemBase] :: MiscFlags -> Word [ioManager] :: MiscFlags -> IoSubSystem [numIoWorkerThreads] :: MiscFlags -> Word32 -- | 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 -> Bool -> DebugFlags -- |
--   s
--   
[scheduler] :: DebugFlags -> Bool -- |
--   i
--   
[interpreter] :: DebugFlags -> Bool -- |
--   w
--   
[weak] :: DebugFlags -> Bool -- |
--   G
--   
[gccafs] :: DebugFlags -> Bool -- |
--   g
--   
[gc] :: DebugFlags -> Bool -- |
--   n
--   
[nonmoving_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 HeapByInfoTable :: 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 [startHeapProfileAtStartup] :: 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 -> 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 nonmoving GC heap census samples [traceNonmovingGc] :: 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 -- | The I/O SubSystem to use in the program. data IoSubSystem -- | Use a POSIX I/O Sub-System IoPOSIX :: IoSubSystem -- | Use platform native Sub-System. For unix OSes this is the same as -- IoPOSIX, but on Windows this means use the Windows native APIs for -- I/O, including IOCP and RIO. IoNative :: IoSubSystem getRTSFlags :: IO RTSFlags getGCFlags :: IO GCFlags getConcFlags :: IO ConcFlags getMiscFlags :: IO MiscFlags -- | Needed to optimize support for different IO Managers on Windows. See -- Note [The need for getIoManagerFlag] getIoManagerFlag :: IO IoSubSystem getDebugFlags :: IO DebugFlags getCCFlags :: IO CCFlags getProfFlags :: IO ProfFlags getTraceFlags :: IO TraceFlags getTickyFlags :: IO TickyFlags getParFlags :: IO ParFlags instance GHC.Enum.Enum GHC.RTS.Flags.DoCostCentres instance GHC.Enum.Enum GHC.RTS.Flags.DoHeapProfile instance GHC.Enum.Enum GHC.RTS.Flags.DoTrace instance GHC.Enum.Enum GHC.RTS.Flags.GiveGCStats instance GHC.Enum.Enum GHC.RTS.Flags.IoSubSystem instance GHC.Classes.Eq GHC.RTS.Flags.IoSubSystem instance GHC.Generics.Generic GHC.RTS.Flags.CCFlags instance GHC.Generics.Generic GHC.RTS.Flags.ConcFlags instance GHC.Generics.Generic GHC.RTS.Flags.DebugFlags instance GHC.Generics.Generic GHC.RTS.Flags.DoCostCentres instance GHC.Generics.Generic GHC.RTS.Flags.DoHeapProfile instance GHC.Generics.Generic GHC.RTS.Flags.DoTrace instance GHC.Generics.Generic GHC.RTS.Flags.GCFlags instance GHC.Generics.Generic GHC.RTS.Flags.GiveGCStats instance GHC.Generics.Generic GHC.RTS.Flags.MiscFlags instance GHC.Generics.Generic GHC.RTS.Flags.ParFlags instance GHC.Generics.Generic GHC.RTS.Flags.ProfFlags instance GHC.Generics.Generic GHC.RTS.Flags.RTSFlags instance GHC.Generics.Generic GHC.RTS.Flags.TickyFlags instance GHC.Generics.Generic GHC.RTS.Flags.TraceFlags instance GHC.Show.Show GHC.RTS.Flags.CCFlags instance GHC.Show.Show GHC.RTS.Flags.ConcFlags instance GHC.Show.Show GHC.RTS.Flags.DebugFlags instance GHC.Show.Show GHC.RTS.Flags.DoCostCentres instance GHC.Show.Show GHC.RTS.Flags.DoHeapProfile instance GHC.Show.Show GHC.RTS.Flags.DoTrace instance GHC.Show.Show GHC.RTS.Flags.GCFlags instance GHC.Show.Show GHC.RTS.Flags.GiveGCStats instance GHC.Show.Show GHC.RTS.Flags.IoSubSystem instance GHC.Show.Show GHC.RTS.Flags.MiscFlags instance GHC.Show.Show GHC.RTS.Flags.ParFlags instance GHC.Show.Show GHC.RTS.Flags.ProfFlags instance GHC.Show.Show GHC.RTS.Flags.RTSFlags instance GHC.Show.Show GHC.RTS.Flags.TickyFlags instance GHC.Show.Show GHC.RTS.Flags.TraceFlags instance Foreign.Storable.Storable GHC.RTS.Flags.IoSubSystem -- | The SubSystem control interface. These methods can be used to -- disambiguate between the two operations. module GHC.IO.SubSystem withIoSubSystem :: (IoSubSystem -> IO a) -> IO a withIoSubSystem' :: (IoSubSystem -> a) -> a whenIoSubSystem :: IoSubSystem -> IO () -> IO () ioSubSystem :: IoSubSystem -- | The I/O SubSystem to use in the program. data IoSubSystem -- | Use a POSIX I/O Sub-System IoPOSIX :: IoSubSystem -- | Use platform native Sub-System. For unix OSes this is the same as -- IoPOSIX, but on Windows this means use the Windows native APIs for -- I/O, including IOCP and RIO. IoNative :: IoSubSystem -- | Conditionally execute an action depending on the configured I/O -- subsystem. On POSIX systems always execute the first action. On -- Windows execute the second action if WINIO as active, otherwise fall -- back to the first action. conditional :: a -> a -> a -- | Infix version of conditional. posix ! windows == -- conditional posix windows () :: a -> a -> a infixl 7 isWindowsNativeIO :: Bool -- | 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 :: 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.Exception.Type.Exception Data.Dynamic.Dynamic instance GHC.Show.Show 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 would be difficult to correct while continuing to support -- threadStatus. data ThreadId ThreadId :: ThreadId# -> ThreadId -- | Map a thread to an integer identifier which is unique within the -- current process. fromThreadId :: ThreadId -> Word64 showThreadId :: ThreadId -> String -- | 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 () -- | 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. 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). It also emits an event to the RTS -- eventlog. labelThread :: ThreadId -> String -> IO () -- | labelThreadByteArray# sets the label of a thread to the given -- UTF-8 encoded string contained in a ByteArray#. labelThreadByteArray# :: ThreadId -> ByteArray# -> 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) -- | List the Haskell threads of the current process. listThreads :: IO [ThreadId] -- | Query the label of thread, returning Nothing if the thread's -- label has not been set. threadLabel :: ThreadId -> IO (Maybe String) -- | 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 -- | Query the current execution status of a thread. 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) -- | Creates a new thread to run the IO computation passed as the -- first argument, and returns the ThreadId of the newly created -- thread. -- -- The new thread will be a lightweight, unbound thread. Foreign -- calls made by this thread are not guaranteed to be made by any -- particular OS thread; if you need foreign calls to be made by a -- particular OS thread, then use forkOS instead. -- -- The new thread inherits the masked state of the parent (see -- mask). -- -- The newly created thread has an exception handler that discards the -- exceptions BlockedIndefinitelyOnMVar, -- BlockedIndefinitelyOnSTM, and ThreadKilled, and passes -- all other exceptions to the uncaught exception handler. -- -- WARNING: Exceptions in the new thread will not be rethrown in the -- thread that created it. This means that you might be completely -- unaware of the problem if/when this happens. You may want to use the -- async library instead. 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 () 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 () -- | 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 a -> 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. -- -- Using atomically inside an unsafePerformIO or -- unsafeInterleaveIO subverts some of guarantees that STM -- provides. It makes it possible to run a transaction inside of another -- transaction, depending on when the thunk is evaluated. If a nested -- transaction is attempted, an exception is thrown by the runtime. It is -- possible to safely use atomically inside unsafePerformIO -- or unsafeInterleaveIO, but the typechecker does not rule out -- programs that may attempt nested transactions, meaning that the -- programmer must take special care to prevent these. -- -- However, there are functions for creating transactional variables that -- can always be safely called in unsafePerformIO. See: -- newTVarIO, newTChanIO, newBroadcastTChanIO, -- newTQueueIO, newTBQueueIO, and newTMVarIO. -- -- Using unsafePerformIO inside of atomically is also -- dangerous but for different reasons. See unsafeIOToSTM for more -- on this. 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 updated. (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. If the exception is caught via -- catchSTM, only the changes enclosed by the catch are rolled -- back; changes made outside of catchSTM persist. -- -- If the exception is not caught inside of the STM, it is -- re-thrown by atomically, and the entire STM is rolled -- back. -- -- 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 m f catches any exception thrown by -- m using throwSTM, using the function f to -- handle the exception. If an exception is thrown, any changes made by -- m are rolled back, but changes prior to m persist. catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a -- | 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 -- | Provide an IO action with the current value of an MVar. -- The MVar will be empty for the duration that the action is -- running. withMVar :: MVar a -> (a -> IO b) -> IO b -- | Modify the value of an MVar. 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.Base.Alternative GHC.Conc.Sync.STM instance GHC.Base.Applicative GHC.Conc.Sync.STM instance GHC.Classes.Eq GHC.Conc.Sync.BlockReason instance GHC.Classes.Eq (GHC.Conc.Sync.TVar a) instance GHC.Classes.Eq GHC.Conc.Sync.ThreadId instance GHC.Classes.Eq GHC.Conc.Sync.ThreadStatus instance GHC.Base.Functor GHC.Conc.Sync.STM instance GHC.Base.MonadPlus GHC.Conc.Sync.STM instance GHC.Base.Monad GHC.Conc.Sync.STM instance GHC.Base.Monoid a => GHC.Base.Monoid (GHC.Conc.Sync.STM a) instance GHC.Classes.Ord GHC.Conc.Sync.BlockReason instance GHC.Classes.Ord GHC.Conc.Sync.ThreadId instance GHC.Classes.Ord GHC.Conc.Sync.ThreadStatus instance GHC.Base.Semigroup a => GHC.Base.Semigroup (GHC.Conc.Sync.STM a) instance GHC.Show.Show GHC.Conc.Sync.BlockReason instance GHC.Show.Show GHC.Conc.Sync.ThreadId instance GHC.Show.Show GHC.Conc.Sync.ThreadStatus -- | 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 exception thrown when an infinite cycle is detected in -- fixIO. data FixIOException FixIOException :: FixIOException -- | 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 first -- String is the argument given to error, second -- String is the location. data ErrorCall ErrorCallWithLocation :: String -> String -> ErrorCall pattern ErrorCall :: 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 -- | Thrown when the program attempts a continuation capture, but no prompt -- with the given prompt tag exists in the current continuation. data NoMatchingContinuationPrompt NoMatchingContinuationPrompt :: NoMatchingContinuationPrompt -- | 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` ()  ===> throw e
--   throwIO e `seq` ()  ===> ()
--   
-- -- 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 operations, whereas -- throw does not. We say that throwIO throws *precise* -- exceptions and throw, error, etc. all throw *imprecise* -- exceptions. For example -- --
--   throw e + error "boom" ===> error "boom"
--   throw e + error "boom" ===> throw e
--   
-- -- are both valid reductions and the compiler may pick any (loop, even), -- whereas -- --
--   throwIO e >> error "boom" ===> throwIO e
--   
-- -- will always throw e when executed. -- -- See also the GHC wiki page on precise exceptions for a more -- technical introduction to how GHC optimises around precise vs. -- imprecise exceptions. 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. -- -- WARNING: You may want to use throwIO instead so that your -- pure code stays exception-free. throw :: forall a e. 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 propagated further up. If -- you call it again, you might get 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 then it will be propagated 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 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 wraps the release action with mask, which is sufficient -- to ensure that the release action executes to completion when it does -- not invoke any interruptible actions, even in the presence of -- asynchronous exceptions. For example, hClose is -- uninterruptible when it is not racing other uses of the handle. -- Similarly, closing a socket (from "network" package) is also -- uninterruptible under similar conditions. An example of an -- interruptible action is killThread. Completion of interruptible -- release actions can be ensured by wrapping them in -- uninterruptibleMask_, but this risks making the program -- non-responsive to Control-C, or timeouts. Another option is -- to run the release action asynchronously in its own thread: -- --
--   void $ uninterruptibleMask_ $ forkIO $ do { ... }
--   
-- -- The resource will be released as soon as possible, but the thread that -- invoked bracket will not block in an uninterruptible state. 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 impossibleError :: Addr# -> a impossibleConstraintError :: Addr# -> a nonExhaustiveGuardsError :: Addr# -> a patError :: Addr# -> a noMethodBindingError :: Addr# -> a typeError :: Addr# -> a nonTermination :: SomeException nestedAtomically :: SomeException noMatchingContinuationPrompt :: SomeException instance GHC.Exception.Type.Exception Control.Exception.Base.NestedAtomically instance GHC.Exception.Type.Exception Control.Exception.Base.NoMatchingContinuationPrompt instance GHC.Exception.Type.Exception Control.Exception.Base.NoMethodError instance GHC.Exception.Type.Exception Control.Exception.Base.NonTermination instance GHC.Exception.Type.Exception Control.Exception.Base.PatternMatchFail instance GHC.Exception.Type.Exception Control.Exception.Base.RecConError instance GHC.Exception.Type.Exception Control.Exception.Base.RecSelError instance GHC.Exception.Type.Exception Control.Exception.Base.RecUpdError instance GHC.Exception.Type.Exception Control.Exception.Base.TypeError instance GHC.Show.Show Control.Exception.Base.NestedAtomically instance GHC.Show.Show Control.Exception.Base.NoMatchingContinuationPrompt instance GHC.Show.Show Control.Exception.Base.NoMethodError instance GHC.Show.Show Control.Exception.Base.NonTermination instance GHC.Show.Show Control.Exception.Base.PatternMatchFail instance GHC.Show.Show Control.Exception.Base.RecConError instance GHC.Show.Show Control.Exception.Base.RecSelError instance GHC.Show.Show Control.Exception.Base.RecUpdError instance GHC.Show.Show Control.Exception.Base.TypeError -- | 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 -- | An error indicating that the operation failed because the resource -- vanished. See resourceVanishedErrorType. isResourceVanishedError :: 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 the resource vanished. -- This happens when, for example, attempting to write to a closed socket -- or attempting to write to a named pipe that was deleted. resourceVanishedErrorType :: 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 -- | I/O error where the operation failed because the resource vanished. -- See resourceVanishedErrorType. isResourceVanishedErrorType :: 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 first -- String is the argument given to error, second -- String is the location. data ErrorCall ErrorCallWithLocation :: String -> String -> ErrorCall pattern ErrorCall :: 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. -- -- WARNING: You may want to use throwIO instead so that your -- pure code stays exception-free. throw :: forall a e. 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` ()  ===> throw e
--   throwIO e `seq` ()  ===> ()
--   
-- -- 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 operations, whereas -- throw does not. We say that throwIO throws *precise* -- exceptions and throw, error, etc. all throw *imprecise* -- exceptions. For example -- --
--   throw e + error "boom" ===> error "boom"
--   throw e + error "boom" ===> throw e
--   
-- -- are both valid reductions and the compiler may pick any (loop, even), -- whereas -- --
--   throwIO e >> error "boom" ===> throwIO e
--   
-- -- will always throw e when executed. -- -- See also the GHC wiki page on precise exceptions for a more -- technical introduction to how GHC optimises around precise vs. -- imprecise exceptions. 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 propagated further up. If -- you call it again, you might get 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 then it will be propagated 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 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 wraps the release action with mask, which is sufficient -- to ensure that the release action executes to completion when it does -- not invoke any interruptible actions, even in the presence of -- asynchronous exceptions. For example, hClose is -- uninterruptible when it is not racing other uses of the handle. -- Similarly, closing a socket (from "network" package) is also -- uninterruptible under similar conditions. An example of an -- interruptible action is killThread. Completion of interruptible -- release actions can be ensured by wrapping them in -- uninterruptibleMask_, but this risks making the program -- non-responsive to Control-C, or timeouts. Another option is -- to run the release action asynchronously in its own thread: -- --
--   void $ uninterruptibleMask_ $ forkIO $ do { ... }
--   
-- -- The resource will be released as soon as possible, but the thread that -- invoked bracket will not block in an uninterruptible state. 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! -- -- WARNING: If you're looking for "a way to get a String from an -- 'IO String'", then unsafePerformIO is not the way to go. Learn -- about do-notation and the <- syntax element before you -- proceed. 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 -- | This module provides text encoding/decoding using iconv module GHC.IO.Encoding.Iconv iconvEncoding :: String -> IO (Maybe TextEncoding) -- | Construct an iconv-based TextEncoding for the given character -- set and CodingFailureMode. -- -- As iconv is missing in some minimal environments (e.g. #10298), this -- checks to ensure that iconv is working properly before returning the -- encoding, returning Nothing if not. mkIconvEncoding :: CodingFailureMode -> String -> IO (Maybe TextEncoding) localeEncodingName :: String -- | Text codecs for I/O module GHC.IO.Encoding data BufferCodec from to state BufferCodec# :: CodeBuffer# from to -> (Buffer from -> Buffer to -> State# RealWorld -> (# State# RealWorld, 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 -> State# RealWorld -> (# State# RealWorld, 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 () pattern BufferCodec :: CodeBuffer from to -> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to)) -> IO () -> IO state -> (state -> IO ()) -> BufferCodec from to state -- | 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 (little-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 (little-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 encoding of the current locale, but allowing arbitrary undecodable -- bytes to be round-tripped through it. -- -- Do not expect the encoding to be Unicode-compatible: it could appear -- to be ASCII or anything else. -- -- 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 -- | Set locale encoding for your program. The locale affects how -- Chars are encoded and decoded when serialized to bytes: e. g., -- when you read or write files (readFile', writeFile) or -- use standard input/output (getLine, putStrLn). For -- instance, if your program prints non-ASCII characters, it is prudent -- to execute -- --
--   setLocaleEncoding utf8
--   
-- -- This is necessary, but not enough on Windows, where console is a -- stateful device, which needs to be configured using -- System.Win32.Console.setConsoleOutputCP and restored back -- afterwards. These intricacies are covered by code-page package, -- which offers a crossplatform System.IO.CodePage.withCodePage -- bracket. -- -- Wrong locale encoding typically causes error messages like "invalid -- argument (cannot decode byte sequence starting from ...)" or "invalid -- argument (cannot encode character ...)". 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 -- criterion, 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 -- | Internal encoding of argv argvEncoding :: 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] -- | A cost-centre stack from GHC's cost-center profiler. data CostCentreStack -- | A cost-centre from GHC's cost-center profiler. data CostCentre -- | Returns the current CostCentreStack (value is nullPtr -- if the current program was not compiled with profiling support). Takes -- a dummy argument which can be used to avoid the call to -- getCurrentCCS being floated out by the simplifier, which -- would result in an uninformative stack (CAF). getCurrentCCS :: dummy -> IO (Ptr CostCentreStack) -- | Get the CostCentreStack associated with the given value. getCCSOf :: a -> IO (Ptr CostCentreStack) -- | Run a computation with an empty cost-center stack. For example, this -- is used by the interpreter to run an interpreted computation without -- the call stack showing that it was invoked from GHC. clearCCS :: IO a -> IO a -- | Get the CostCentre at the head of a CostCentreStack. ccsCC :: Ptr CostCentreStack -> IO (Ptr CostCentre) -- | Get the tail of a CostCentreStack. ccsParent :: Ptr CostCentreStack -> IO (Ptr CostCentreStack) -- | Get the label of a CostCentre. ccLabel :: Ptr CostCentre -> IO CString -- | Get the module of a CostCentre. ccModule :: Ptr CostCentre -> IO CString -- | Get the source span of a CostCentre. ccSrcSpan :: Ptr CostCentre -> IO CString -- | Format a CostCentreStack as a list of lines. 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 -- --
--   putStrLnWithCallStack :: HasCallStack => String -> IO ()
--   
-- -- as a variant of putStrLn that will get its call-site and -- print it, along with the string given as argument. We can access the -- call-stack inside putStrLnWithCallStack with -- callStack. -- --
--   >>> :{
--   putStrLnWithCallStack :: HasCallStack => String -> IO ()
--   putStrLnWithCallStack msg = do
--     putStrLn msg
--     putStrLn (prettyCallStack callStack)
--   :}
--   
-- -- Thus, if we call putStrLnWithCallStack we will get a -- formatted call-stack alongside our string. -- --
--   >>> putStrLnWithCallStack "hello"
--   hello
--   CallStack (from HasCallStack):
--     putStrLnWithCallStack, called at <interactive>:... in interactive:Ghci...
--   
-- -- 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 -- | A cost-centre stack from GHC's cost-center profiler. data CostCentreStack -- | A cost-centre from GHC's cost-center profiler. data CostCentre -- | Returns the current CostCentreStack (value is nullPtr -- if the current program was not compiled with profiling support). Takes -- a dummy argument which can be used to avoid the call to -- getCurrentCCS being floated out by the simplifier, which -- would result in an uninformative stack (CAF). getCurrentCCS :: dummy -> IO (Ptr CostCentreStack) -- | Get the CostCentreStack associated with the given value. getCCSOf :: a -> IO (Ptr CostCentreStack) -- | Run a computation with an empty cost-center stack. For example, this -- is used by the interpreter to run an interpreted computation without -- the call stack showing that it was invoked from GHC. clearCCS :: IO a -> IO a -- | Get the CostCentre at the head of a CostCentreStack. ccsCC :: Ptr CostCentreStack -> IO (Ptr CostCentre) -- | Get the tail of a CostCentreStack. ccsParent :: Ptr CostCentreStack -> IO (Ptr CostCentreStack) -- | Get the label of a CostCentre. ccLabel :: Ptr CostCentre -> IO CString -- | Get the module of a CostCentre. ccModule :: Ptr CostCentre -> IO CString -- | Get the source span of a CostCentre. ccSrcSpan :: Ptr CostCentre -> IO CString -- | Format a CostCentreStack as a list of lines. ccsToStrings :: Ptr CostCentreStack -> IO [String] renderStack :: [String] -> String -- | Access to GHC's info-table provenance metadata. module GHC.InfoProv data InfoProv InfoProv :: String -> String -> String -> String -> String -> String -> String -> InfoProv [ipName] :: InfoProv -> String [ipDesc] :: InfoProv -> String [ipTyDesc] :: InfoProv -> String [ipLabel] :: InfoProv -> String [ipMod] :: InfoProv -> String [ipSrcFile] :: InfoProv -> String [ipSrcSpan] :: InfoProv -> String ipLoc :: InfoProv -> String ipeProv :: Ptr InfoProvEnt -> Ptr InfoProv -- | Get information about where a value originated from. This information -- is stored statically in a binary when `-finfo-table-map` is enabled. -- The source positions will be greatly improved by also enabled debug -- information with `-g3`. Finally you can enable -- `-fdistinct-constructor-tables` to get more precise information about -- data constructor allocations. -- -- The information is collect by looking at the info table address of a -- specific closure and then consulting a specially generated map (by -- `-finfo-table-map`) to find out where we think the best source -- position to describe that info table arose from. whereFrom :: a -> IO (Maybe InfoProv) data InfoProvEnt peekInfoProv :: Ptr InfoProv -> IO InfoProv instance GHC.Classes.Eq GHC.InfoProv.InfoProv instance GHC.Show.Show GHC.InfoProv.InfoProv -- | This module defines the basic operations on I/O "handles". All of the -- operations defined here are independent of the underlying device. module GHC.IO.Handle.Internals withHandle :: String -> Handle -> (Handle__ -> IO (Handle__, a)) -> IO a withHandle' :: String -> Handle -> MVar Handle__ -> (Handle__ -> IO (Handle__, a)) -> IO a withHandle_ :: String -> Handle -> (Handle__ -> IO a) -> IO a withHandle__' :: String -> Handle -> MVar Handle__ -> (Handle__ -> IO Handle__) -> IO () withHandle_' :: String -> Handle -> MVar Handle__ -> (Handle__ -> IO a) -> IO a withAllHandles__ :: String -> Handle -> (Handle__ -> IO Handle__) -> IO () wantWritableHandle :: String -> Handle -> (Handle__ -> IO a) -> IO a wantReadableHandle :: String -> Handle -> (Handle__ -> IO (Handle__, a)) -> IO a wantReadableHandle_ :: String -> Handle -> (Handle__ -> IO a) -> IO a wantSeekableHandle :: String -> Handle -> (Handle__ -> IO a) -> IO a mkHandle :: (RawIO dev, IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> HandleType -> Bool -> Maybe TextEncoding -> NewlineMode -> Maybe HandleFinalizer -> Maybe (MVar Handle__) -> IO Handle -- | makes a new Handle mkFileHandle :: (RawIO dev, IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> IOMode -> Maybe TextEncoding -> NewlineMode -> IO Handle -- | makes a new Handle without a finalizer. mkFileHandleNoFinalizer :: (RawIO dev, 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 :: (RawIO dev, IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> 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. mkDuplexHandleNoFinalizer :: (RawIO dev, IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle -- | Add a finalizer to a Handle. Specifically, the finalizer will -- be added to the MVar of a file handle or the write-side -- MVar of a duplex handle. See Handle Finalizers for details. addHandleFinalizer :: Handle -> HandleFinalizer -> IO () openTextEncoding :: Maybe TextEncoding -> HandleType -> (forall es ds. () => Maybe (TextEncoder es) -> Maybe (TextDecoder ds) -> IO a) -> IO a closeTextCodecs :: Handle__ -> IO () initBufferState :: HandleType -> BufferState dEFAULT_CHAR_BUFFER_SIZE :: Int -- | syncs the file with the buffer, including moving the file pointer -- backwards in the case of a read buffer. This can fail on a -- non-seekable read Handle. flushBuffer :: Handle__ -> IO () flushWriteBuffer :: Handle__ -> IO () flushCharReadBuffer :: Handle__ -> IO () -- | flushes the Char buffer only. Works on all Handles. flushCharBuffer :: Handle__ -> IO () flushByteReadBuffer :: Handle__ -> IO () flushByteWriteBuffer :: Handle__ -> IO () readTextDevice :: Handle__ -> CharBuffer -> IO CharBuffer writeCharBuffer :: Handle__ -> CharBuffer -> IO () readTextDeviceNonBlocking :: Handle__ -> CharBuffer -> IO CharBuffer decodeByteBuf :: Handle__ -> CharBuffer -> IO CharBuffer augmentIOError :: IOException -> String -> Handle -> IOException ioe_closedHandle :: IO a ioe_semiclosedHandle :: IO a ioe_EOF :: IO a ioe_notReadable :: IO a ioe_notWritable :: IO a ioe_finalizedHandle :: FilePath -> Handle__ ioe_bufsiz :: Int -> IO a -- | This function exists temporarily to avoid an unused import warning in -- bytestring. hClose_impl :: Handle -> IO () hClose_help :: Handle__ -> IO (Handle__, Maybe SomeException) hLookAhead_ :: Handle__ -> IO Char type HandleFinalizer = FilePath -> MVar Handle__ -> IO () handleFinalizer :: FilePath -> MVar Handle__ -> IO () debugIO :: String -> IO () traceIO :: String -> IO () 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] -- | String I/O functions module GHC.IO.Handle.Text -- | 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. hGetLine does not return the -- newline as part of the result. -- -- A line is separated by the newline set with hSetNewlineMode or -- nativeNewline by default. The read newline character(s) are not -- returned as part of the result. -- -- If hGetLine encounters end-of-file at any point while reading -- in the middle of a line, it is treated as a line terminator and the -- (partial) line is returned. -- -- This operation may fail with: -- -- -- --

Examples

-- --
--   >>> withFile "/home/user/foo" ReadMode hGetLine >>= putStrLn
--   this is the first line of the file :O
--   
-- --
--   >>> withFile "/home/user/bar" ReadMode (replicateM 3 . hGetLine)
--   ["this is the first line","this is the second line","this is the third line"]
--   
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 () commitBuffer' :: RawCharBuffer -> Int -> Int -> Bool -> Bool -> Handle__ -> IO CharBuffer -- | 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 -- | 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 memcpy :: Ptr a -> Ptr a -> CSize -> IO (Ptr ()) -- | The same as hPutStr, but adds a newline character. hPutStrLn :: Handle -> String -> IO () -- | The hGetContents' operation reads all input on the given handle -- before returning it as a String and closing the handle. hGetContents' :: Handle -> 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 to perform larger atomic operations such as reading from multiple -- variables: use STM instead. -- -- In particular, the "bigger" functions in this module (swapMVar, -- withMVar, modifyMVar_ and modifyMVar) are simply -- the composition of a takeMVar followed by a putMVar with -- exception safety. These have atomicity guarantees only 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 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 it is 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. In other words, it cannot -- guarantee that, by the time swapMVar gets the chance to write -- to the MVar, the value of the MVar has not been altered by a write -- operation from another thread. 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. In other words, it -- cannot guarantee that, by the time withMVar gets the chance to -- write to the MVar, the value of the MVar has not been altered by a -- write operation from another thread. 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. In other words, it cannot guarantee -- that, by the time modifyMVar_ gets the chance to write to the -- MVar, the value of the MVar has not been altered by a write operation -- from another thread. 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 () -- | Interrupts the current wait of the I/O manager if it is currently -- blocked. This instructs it to re-read how much it should wait and to -- process any pending events. interruptIOManager :: 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. -- -- Be careful not to exceed maxBound :: Int, which on 32-bit -- machines is only 2147483647 μs, less than 36 minutes. Consider using -- Control.Concurrent.Thread.Delay.delay from -- unbounded-delays package. threadDelay :: Int -> IO () -- | Switch the value of returned TVar from initial value -- False to True after a given number of microseconds. The -- caveats associated with threadDelay also apply. -- -- Be careful not to exceed maxBound :: Int, which on 32-bit -- machines is only 2147483647 μs, less than 36 minutes. 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 () -- | Raw read/write operations on file descriptors module GHC.IO.FD data FD FD :: {-# UNPACK #-} !CInt -> {-# UNPACK #-} !Int -> FD [fdFD] :: FD -> {-# UNPACK #-} !CInt [fdIsNonBlocking] :: FD -> {-# UNPACK #-} !Int -- | Open a file and make an FD for it. Truncates the file to zero -- size when the IOMode is WriteMode. -- -- openFileWith takes two actions, act1 and -- act2, to perform after opening the file. -- -- act1 is passed a file descriptor and I/O device type for the -- newly opened file. If an exception occurs in act1, then the -- file will be closed. act1 must not close the file -- itself. If it does so and then receives an exception, then the -- exception handler will attempt to close it again, which is -- impermissible. -- -- act2 is performed with asynchronous exceptions masked. It is -- passed a function to restore the masking state and the result of -- act1. It /must not/ throw an exception (or deliver one via an -- interruptible operation) without first closing the file or arranging -- for it to be closed. act2 may close the file, but is -- not required to do so. If act2 leaves the file open, then the -- file will remain open on return from openFileWith. -- -- Code calling openFileWith that wishes to install a finalizer to -- close the file should do so in act2. Doing so in -- act1 could potentially close the file in the finalizer first -- and then in the exception handler. See openFile' for an example -- of this use. Regardless, the caller is responsible for ensuring that -- the file is eventually closed, perhaps using bracket. openFileWith :: FilePath -> IOMode -> Bool -> (FD -> IODeviceType -> IO r) -> ((forall x. () => IO x -> IO x) -> r -> IO s) -> IO s -- | Open a file and make an FD for it. Truncates the file to zero -- size when the IOMode is WriteMode. This function is -- difficult to use without potentially leaking the file descriptor on -- exception. In particular, it must be used with exceptions masked, -- which is a bit rude because the thread will be uninterruptible while -- the file path is being encoded. Use openFileWith instead. openFile :: FilePath -> IOMode -> Bool -> IO (FD, IODeviceType) -- | Make a FD from an existing file descriptor. Fails if the FD -- refers to a directory. If the FD refers to a file, mkFD locks -- the file according to the Haskell 2010 single writer/multiple reader -- locking semantics (this is why we need the IOMode argument -- too). mkFD :: CInt -> IOMode -> Maybe (IODeviceType, CDev, CIno) -> Bool -> Bool -> IO (FD, IODeviceType) release :: FD -> IO () setNonBlockingMode :: FD -> Bool -> IO FD readRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO Int readRawBufferPtrNoBlock :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO Int writeRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt stdin :: FD stdout :: FD stderr :: FD instance GHC.IO.BufferedIO.BufferedIO GHC.IO.FD.FD instance GHC.IO.Device.IODevice GHC.IO.FD.FD instance GHC.IO.Device.RawIO GHC.IO.FD.FD instance GHC.Show.Show GHC.IO.FD.FD -- | 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: -- -- -- -- On POSIX systems, openFile is an interruptible operation -- as described in Control.Exception. -- -- Note: if you will be working with files containing binary data, you'll -- want to be using openBinaryFile. openFile :: FilePath -> IOMode -> IO Handle -- | withFile name mode act opens a file like -- 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 -- | 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 -- | A version of openBinaryFile that takes an action to perform -- with the handle. If an exception occurs in the action, then the file -- will be closed automatically. The action should close the file -- when finished with it so the file does not remain open until the -- garbage collector collects the handle. withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r -- | 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. -- -- Note: when blocking happens, an OS thread becomes tied up with the -- processing, so the program must have at least another OS thread if it -- wants to unblock itself. By corollary, a non-threaded runtime will -- need a process-external trigger in order to become unblocked. -- -- On POSIX systems, openFileBlocking is an interruptible -- operation as described in Control.Exception. openFileBlocking :: FilePath -> IOMode -> IO Handle -- | withFileBlocking name mode act opens a file like -- openFileBlocking and passes the resulting handle to the -- computation act. The handle will be closed on exit from -- withFileBlocking, 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. withFileBlocking :: FilePath -> IOMode -> (Handle -> IO r) -> IO r 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 -- | This model abstracts away the platform specific handles that can be -- toggled through the RTS. module GHC.IO.StdHandles stdin :: Handle stdout :: Handle stderr :: Handle openFile :: FilePath -> IOMode -> IO Handle openBinaryFile :: FilePath -> IOMode -> IO Handle openFileBlocking :: FilePath -> IOMode -> IO Handle withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r withFileBlocking :: FilePath -> IOMode -> (Handle -> IO r) -> IO r 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 platforms 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. -- -- Returns True if taking the lock was successful and False -- otherwise. hTryLock :: Handle -> LockMode -> IO Bool -- | Release a lock taken with hLock or hTryLock. hUnlock :: Handle -> IO () -- | 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 :: (RawIO dev, 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 :: (RawIO dev, 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 -- buffered 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 is an interruptible operation in the sense -- described in Control.Exception. If hClose is interrupted -- by an asynchronous exception in the process of flushing its buffers, -- then the I/O device (e.g., file) will be closed anyway. 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 platforms 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. -- -- Returns True if taking the lock was successful and False -- otherwise. 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? -- -- On Windows the result of hIsTerminalDevide might be -- misleading, because non-native terminals, such as MinTTY used in MSYS -- and Cygwin environments, are implemented via redirection. Use -- System.Win32.Types.withHandleToHANDLE -- System.Win32.MinTTY.isMinTTYHandle to recognise it. Also consider -- ansi-terminal package for crossplatform terminal support. 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 representation 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. hGetLine does not return the -- newline as part of the result. -- -- A line is separated by the newline set with hSetNewlineMode or -- nativeNewline by default. The read newline character(s) are not -- returned as part of the result. -- -- If hGetLine encounters end-of-file at any point while reading -- in the middle of a line, it is treated as a line terminator and the -- (partial) line is returned. -- -- This operation may fail with: -- -- -- --

Examples

-- --
--   >>> withFile "/home/user/foo" ReadMode hGetLine >>= putStrLn
--   this is the first line of the file :O
--   
-- --
--   >>> withFile "/home/user/bar" ReadMode (replicateM 3 . hGetLine)
--   ["this is the first line","this is the second line","this is the third line"]
--   
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 -- | The hGetContents' operation reads all input on the given handle -- before returning it as a String and closing the handle. 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 -- | The implementation of mfix for IO. If the function -- passed to fixIO inspects its argument, the resulting action -- will throw FixIOException. 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 stdin :: Handle stdout :: Handle stderr :: Handle withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r 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 is an interruptible operation in the sense -- described in Control.Exception. If hClose is interrupted -- by an asynchronous exception in the process of flushing its buffers, -- then the I/O device (e.g., file) will be closed anyway. 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 readFile' function reads a file and returns the contents of -- the file as a string. The file is fully read before being returned, 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? -- -- On Windows the result of hIsTerminalDevide might be -- misleading, because non-native terminals, such as MinTTY used in MSYS -- and Cygwin environments, are implemented via redirection. Use -- System.Win32.Types.withHandleToHANDLE -- System.Win32.MinTTY.isMinTTYHandle to recognise it. Also consider -- ansi-terminal package for crossplatform terminal support. 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. hGetLine does not return the -- newline as part of the result. -- -- A line is separated by the newline set with hSetNewlineMode or -- nativeNewline by default. The read newline character(s) are not -- returned as part of the result. -- -- If hGetLine encounters end-of-file at any point while reading -- in the middle of a line, it is treated as a line terminator and the -- (partial) line is returned. -- -- This operation may fail with: -- -- -- --

Examples

-- --
--   >>> withFile "/home/user/foo" ReadMode hGetLine >>= putStrLn
--   this is the first line of the file :O
--   
-- --
--   >>> withFile "/home/user/bar" ReadMode (replicateM 3 . hGetLine)
--   ["this is the first line","this is the second line","this is the third line"]
--   
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 -- | The hGetContents' operation reads all input on the given handle -- before returning it as a String and closing the handle. 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 getContents' operation returns all user input as a single -- string, which is fully read before being returned (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 :: FilePath -> IOMode -> (Handle -> IO r) -> IO r 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 (little-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 (little-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 -- criterion, 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 representation 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 :: Type -> Type) -- | 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. -- -- When f is strict, this means that because, by the definition -- of strictness, f ⊥ = ⊥ and such the least defined fixed point -- of any strict function is . -- --

Examples

-- -- We can write the factorial function using direct recursion as -- --
--   >>> let fac n = if n <= 1 then 1 else n * fac (n-1) in fac 5
--   120
--   
-- -- This uses the fact that Haskell’s let introduces recursive -- bindings. We can rewrite this definition using fix, -- -- Instead of making a recursive call, we introduce a dummy parameter -- rec; when used within fix, this parameter then refers -- to fix’s argument, hence the recursion is reintroduced. -- --
--   >>> fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5
--   120
--   
-- -- Using fix, we can implement versions of repeat as -- fix . (:) and cycle as -- fix . (++) -- --
--   >>> take 10 $ fix (0:)
--   [0,0,0,0,0,0,0,0,0,0]
--   
-- --
--   >>> map (fix (\rec n -> if n < 2 then n else rec (n - 1) + rec (n - 2))) [1..10]
--   [1,1,2,3,5,8,13,21,34,55]
--   
-- --

Implementation Details

-- -- The current implementation of fix uses structural sharing -- --
--   fix f = let x = f x in x
--   
-- -- A more straightforward but non-sharing version would look like -- --
--   fix f = f (fix f)
--   
fix :: (a -> a) -> a instance (Control.Monad.Fix.MonadFix f, Control.Monad.Fix.MonadFix g) => Control.Monad.Fix.MonadFix (f GHC.Generics.:*: g) instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (Data.Semigroup.Internal.Alt f) instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (Data.Monoid.Ap f) instance Control.Monad.Fix.MonadFix Data.Ord.Down instance Control.Monad.Fix.MonadFix Data.Semigroup.Internal.Dual instance Control.Monad.Fix.MonadFix (Data.Either.Either e) instance Control.Monad.Fix.MonadFix ((->) r) instance Control.Monad.Fix.MonadFix Data.Monoid.First instance Control.Monad.Fix.MonadFix GHC.Types.IO instance Control.Monad.Fix.MonadFix Data.Monoid.Last instance Control.Monad.Fix.MonadFix [] instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (GHC.Generics.M1 i c f) instance Control.Monad.Fix.MonadFix GHC.Maybe.Maybe instance Control.Monad.Fix.MonadFix GHC.Base.NonEmpty instance Control.Monad.Fix.MonadFix GHC.Generics.Par1 instance Control.Monad.Fix.MonadFix Data.Semigroup.Internal.Product instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (GHC.Generics.Rec1 f) instance Control.Monad.Fix.MonadFix (GHC.ST.ST s) instance Control.Monad.Fix.MonadFix GHC.Tuple.Prim.Solo instance Control.Monad.Fix.MonadFix Data.Semigroup.Internal.Sum -- | 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 GHC.Base.Applicative Data.Functor.Identity.Identity instance GHC.Bits.Bits a => GHC.Bits.Bits (Data.Functor.Identity.Identity a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Functor.Identity.Identity a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Functor.Identity.Identity a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Functor.Identity.Identity a) instance GHC.Bits.FiniteBits a => GHC.Bits.FiniteBits (Data.Functor.Identity.Identity a) instance GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Identity.Identity a) instance Data.Foldable.Foldable Data.Functor.Identity.Identity instance GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Identity.Identity a) instance GHC.Base.Functor Data.Functor.Identity.Identity instance GHC.Generics.Generic1 Data.Functor.Identity.Identity instance GHC.Generics.Generic (Data.Functor.Identity.Identity a) instance GHC.Real.Integral a => GHC.Real.Integral (Data.Functor.Identity.Identity a) instance GHC.Ix.Ix a => GHC.Ix.Ix (Data.Functor.Identity.Identity a) instance Control.Monad.Fix.MonadFix Data.Functor.Identity.Identity instance GHC.Base.Monad Data.Functor.Identity.Identity instance GHC.Base.Monoid a => GHC.Base.Monoid (Data.Functor.Identity.Identity a) instance GHC.Num.Num a => GHC.Num.Num (Data.Functor.Identity.Identity a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Functor.Identity.Identity a) instance GHC.Read.Read a => GHC.Read.Read (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.Base.Semigroup a => GHC.Base.Semigroup (Data.Functor.Identity.Identity a) instance GHC.Show.Show a => GHC.Show.Show (Data.Functor.Identity.Identity a) instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Data.Functor.Identity.Identity a) -- | 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 :: Type -> Type -> Type) -- | 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') infixr 3 *** infixr 3 &&& -- | Kleisli arrows of a monad. newtype Kleisli (m :: Type -> Type) a b Kleisli :: (a -> m b) -> Kleisli (m :: Type -> Type) a b [runKleisli] :: Kleisli (m :: Type -> Type) 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 (>>>) :: forall {k} cat (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c infixr 1 >>> -- | Right-to-left composition (<<<) :: forall {k} cat (b :: k) (c :: k) (a :: k). 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 :: Type -> Type -> Type) zeroArrow :: ArrowZero a => a b c -- | A monoid on arrows. class ArrowZero a => ArrowPlus (a :: Type -> Type -> Type) -- | An associative operation with identity zeroArrow. (<+>) :: ArrowPlus a => a b c -> a b c -> a b c infixr 5 <+> -- | 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 :: Type -> Type -> Type) -- | 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 infixr 2 ||| infixr 2 +++ -- | 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 :: Type -> Type -> Type) 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 :: Type -> Type -> Type) b ArrowMonad :: a () b -> ArrowMonad (a :: Type -> Type -> Type) 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 :: Type -> Type -> Type) loop :: ArrowLoop a => a (b, d) (c, d) -> a b c instance Control.Arrow.ArrowPlus a => GHC.Base.Alternative (Control.Arrow.ArrowMonad a) instance GHC.Base.Alternative m => GHC.Base.Alternative (Control.Arrow.Kleisli m a) instance Control.Arrow.Arrow a => GHC.Base.Applicative (Control.Arrow.ArrowMonad a) instance GHC.Base.Applicative m => GHC.Base.Applicative (Control.Arrow.Kleisli m 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 Control.Arrow.Arrow (->) instance GHC.Base.Monad m => Control.Arrow.Arrow (Control.Arrow.Kleisli m) instance Control.Arrow.ArrowLoop (->) instance Control.Monad.Fix.MonadFix m => Control.Arrow.ArrowLoop (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 Control.Arrow.Arrow a => GHC.Base.Functor (Control.Arrow.ArrowMonad a) instance GHC.Base.Functor m => GHC.Base.Functor (Control.Arrow.Kleisli m a) instance GHC.Generics.Generic1 (Control.Arrow.Kleisli m a) instance GHC.Generics.Generic (Control.Arrow.Kleisli m a b) instance Control.Arrow.ArrowApply a => GHC.Base.Monad (Control.Arrow.ArrowMonad a) instance GHC.Base.Monad m => GHC.Base.Monad (Control.Arrow.Kleisli m a) instance (Control.Arrow.ArrowApply a, Control.Arrow.ArrowPlus a) => GHC.Base.MonadPlus (Control.Arrow.ArrowMonad a) instance GHC.Base.MonadPlus m => GHC.Base.MonadPlus (Control.Arrow.Kleisli m a) -- | This module describes a structure intermediate between a functor and a -- monad (technically, a strong lax monoidal functor). Compared with -- monads, this interface lacks the full power of the binding operation -- >>=, but -- -- -- -- 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 :: Type -> Type) -- | 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. -- --

Example

-- -- Used in combination with (<$>), -- (<*>) can be used to build a record. -- --
--   >>> data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
--   
-- --
--   >>> produceFoo :: Applicative f => f Foo
--   
-- --
--   >>> produceBar :: Applicative f => f Bar
--   
--   >>> produceBaz :: Applicative f => f Baz
--   
-- --
--   >>> mkState :: Applicative f => f MyState
--   
--   >>> mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz
--   
(<*>) :: 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 <*>. -- -- This became a typeclass method in 4.10.0.0. Prior to that, it was a -- function defined in terms of <*> and fmap. -- --

Example

-- --
--   >>> liftA2 (,) (Just 3) (Just 5)
--   Just (3,5)
--   
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c -- | Sequence actions, discarding the value of the first argument. -- --

Examples

-- -- If used in conjunction with the Applicative instance for Maybe, -- you can chain Maybe computations, with a possible "early return" in -- case of Nothing. -- --
--   >>> Just 2 *> Just 3
--   Just 3
--   
-- --
--   >>> Nothing *> Just 3
--   Nothing
--   
-- -- Of course a more interesting use case would be to have effectful -- computations instead of just returning pure values. -- --
--   >>> import Data.Char
--   
--   >>> import Text.ParserCombinators.ReadP
--   
--   >>> let p = string "my name is " *> munch1 isAlpha <* eof
--   
--   >>> readP_to_S p "my name is Simon"
--   [("Simon","")]
--   
(*>) :: 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 infixl 4 <*> infixl 4 *> infixl 4 <* -- | A monoid on applicative functors. -- -- If defined, some and many should be the least solutions -- of the equations: -- -- class Applicative f => Alternative (f :: Type -> Type) -- | 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] infixl 3 <|> -- | The Const functor. newtype Const a (b :: k) Const :: a -> Const a (b :: k) [getConst] :: Const a (b :: k) -> a newtype WrappedMonad (m :: Type -> Type) a WrapMonad :: m a -> WrappedMonad (m :: Type -> Type) a [unwrapMonad] :: WrappedMonad (m :: Type -> Type) a -> m a newtype WrappedArrow (a :: Type -> Type -> Type) b c WrapArrow :: a b c -> WrappedArrow (a :: Type -> Type -> Type) b c [unwrapArrow] :: WrappedArrow (a :: Type -> Type -> Type) 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. -- --

Examples

-- -- Perform a computation with Maybe and replace the result with a -- constant value if it is Just: -- --
--   >>> 'a' <$ Just 2
--   Just 'a'
--   
--   >>> 'a' <$ Nothing
--   Nothing
--   
(<$) :: Functor f => a -> f b -> f a infixl 4 <$ -- | A variant of <*> with the types of the arguments -- reversed. It differs from flip (<*>) in -- that the effects are resolved in the order the arguments are -- presented. -- --

Examples

-- --
--   >>> (<**>) (print 1) (id <$ print 2)
--   1
--   2
--   
-- --
--   >>> flip (<*>) (print 1) (id <$ print 2)
--   2
--   1
--   
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 <**> -- | Lift a function to actions. Equivalent to Functor's fmap but -- implemented using only Applicative's methods: liftA -- f a = pure f <*> a -- -- As such this function may be used to implement a Functor -- instance from an Applicative one. -- --

Examples

-- -- Using the Applicative instance for Lists: -- --
--   >>> liftA (+1) [1, 2]
--   [2,3]
--   
-- -- Or the Applicative instance for Maybe -- --
--   >>> liftA (+1) (Just 3)
--   Just 4
--   
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. -- -- It is useful for modelling any computation that is allowed to fail. -- --

Examples

-- -- Using the Alternative instance of Control.Monad.Except, -- the following functions: -- --
--   >>> import Control.Monad.Except
--   
-- --
--   >>> canFail = throwError "it failed" :: Except String Int
--   
--   >>> final = return 42                :: Except String Int
--   
-- -- Can be combined by allowing the first function to fail: -- --
--   >>> runExcept $ canFail *> final
--   Left "it failed"
--   
--   >>> runExcept $ optional canFail *> final
--   Right 42
--   
optional :: Alternative f => f a -> f (Maybe a) -- | The sum of a collection of actions using (<|>), -- generalizing concat. -- -- asum is just like msum, but generalised to -- Alternative. -- --

Examples

-- -- Basic usage: -- --
--   >>> asum [Just "Hello", Nothing, Just "World"]
--   Just "Hello"
--   
asum :: (Foldable t, Alternative f) => t (f a) -> f a instance (Control.Arrow.ArrowZero a, Control.Arrow.ArrowPlus a) => GHC.Base.Alternative (Control.Applicative.WrappedArrow a b) instance GHC.Base.MonadPlus m => GHC.Base.Alternative (Control.Applicative.WrappedMonad m) instance GHC.Base.Alternative Control.Applicative.ZipList instance Control.Arrow.Arrow a => GHC.Base.Applicative (Control.Applicative.WrappedArrow a b) instance GHC.Base.Monad m => GHC.Base.Applicative (Control.Applicative.WrappedMonad m) instance GHC.Base.Applicative Control.Applicative.ZipList instance GHC.Classes.Eq a => GHC.Classes.Eq (Control.Applicative.ZipList a) instance Data.Foldable.Foldable Control.Applicative.ZipList instance Control.Arrow.Arrow a => GHC.Base.Functor (Control.Applicative.WrappedArrow a b) instance GHC.Base.Monad m => GHC.Base.Functor (Control.Applicative.WrappedMonad m) instance GHC.Base.Functor Control.Applicative.ZipList instance GHC.Generics.Generic1 (Control.Applicative.WrappedArrow a b) instance GHC.Generics.Generic1 (Control.Applicative.WrappedMonad m) instance GHC.Generics.Generic1 Control.Applicative.ZipList instance GHC.Generics.Generic (Control.Applicative.WrappedArrow a b c) instance GHC.Generics.Generic (Control.Applicative.WrappedMonad m a) instance GHC.Generics.Generic (Control.Applicative.ZipList a) instance GHC.Base.Monad m => GHC.Base.Monad (Control.Applicative.WrappedMonad m) instance GHC.Classes.Ord a => GHC.Classes.Ord (Control.Applicative.ZipList a) instance GHC.Read.Read a => GHC.Read.Read (Control.Applicative.ZipList a) instance GHC.Show.Show a => GHC.Show.Show (Control.Applicative.ZipList a) -- | Class of data structures that can be traversed from left to right, -- performing an action on each element. Instances are expected to -- satisfy the listed laws. module Data.Traversable -- | Functors representing data structures that can be transformed to -- structures of the same shape by performing an -- Applicative (or, therefore, Monad) action on each -- element from left to right. -- -- A more detailed description of what same shape means, the -- various methods, how traversals are constructed, and example advanced -- use-cases can be found in the Overview section of -- Data.Traversable#overview. -- -- For the class laws see the Laws section of -- Data.Traversable#laws. class (Functor t, Foldable t) => Traversable (t :: Type -> Type) -- | 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_. -- --

Examples

-- -- Basic usage: -- -- In the first two examples we show each evaluated action mapping to the -- output structure. -- --
--   >>> traverse Just [1,2,3,4]
--   Just [1,2,3,4]
--   
-- --
--   >>> traverse id [Right 1, Right 2, Right 3, Right 4]
--   Right [1,2,3,4]
--   
-- -- In the next examples, we show that Nothing and Left -- values short circuit the created structure. -- --
--   >>> traverse (const Nothing) [1,2,3,4]
--   Nothing
--   
-- --
--   >>> traverse (\x -> if odd x then Just x else Nothing)  [1,2,3,4]
--   Nothing
--   
-- --
--   >>> traverse id [Right 1, Right 2, Right 3, Right 4, Left 0]
--   Left 0
--   
traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) -- | Evaluate each action in the structure from left to right, and collect -- the results. For a version that ignores the results see -- sequenceA_. -- --

Examples

-- -- Basic usage: -- -- For the first two examples we show sequenceA fully evaluating a a -- structure and collecting the results. -- --
--   >>> sequenceA [Just 1, Just 2, Just 3]
--   Just [1,2,3]
--   
-- --
--   >>> sequenceA [Right 1, Right 2, Right 3]
--   Right [1,2,3]
--   
-- -- The next two example show Nothing and Just will short -- circuit the resulting structure if present in the input. For more -- context, check the Traversable instances for Either and -- Maybe. -- --
--   >>> sequenceA [Just 1, Just 2, Just 3, Nothing]
--   Nothing
--   
-- --
--   >>> sequenceA [Right 1, Right 2, Right 3, Left 4]
--   Left 4
--   
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_. -- --

Examples

-- -- mapM is literally a traverse with a type signature -- restricted to Monad. Its implementation may be more efficient -- due to additional power of Monad. 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_. -- --

Examples

-- -- Basic usage: -- -- The first two examples are instances where the input and and output of -- sequence are isomorphic. -- --
--   >>> sequence $ Right [1,2,3,4]
--   [Right 1,Right 2,Right 3,Right 4]
--   
-- --
--   >>> sequence $ [Right 1,Right 2,Right 3,Right 4]
--   Right [1,2,3,4]
--   
-- -- The following examples demonstrate short circuit behavior for -- sequence. -- --
--   >>> sequence $ Left [1,2,3,4]
--   Left [1,2,3,4]
--   
-- --
--   >>> sequence $ [Left 0, Right 1,Right 2,Right 3,Right 4]
--   Left 0
--   
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) -- | forAccumM is mapAccumM with the arguments rearranged. forAccumM :: (Monad m, Traversable t) => s -> t a -> (s -> a -> m (s, b)) -> m (s, 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. -- --

Examples

-- -- Basic usage: -- --
--   >>> mapAccumL (\a b -> (a + b, a)) 0 [1..10]
--   (55,[0,1,3,6,10,15,21,28,36,45])
--   
-- --
--   >>> mapAccumL (\a b -> (a <> show b, a)) "0" [1..5]
--   ("012345",["0","01","012","0123","01234"])
--   
mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) -- | 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. -- --

Examples

-- -- Basic usage: -- --
--   >>> mapAccumR (\a b -> (a + b, a)) 0 [1..10]
--   (55,[54,52,49,45,40,34,27,19,10,0])
--   
-- --
--   >>> mapAccumR (\a b -> (a <> show b, a)) "0" [1..5]
--   ("054321",["05432","0543","054","05","0"])
--   
mapAccumR :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) -- | The mapAccumM function behaves like a combination of -- mapM and mapAccumL that traverses the structure while -- evaluating the actions and passing an accumulating parameter from left -- to right. It returns a final value of this accumulator together with -- the new structure. The accummulator is often used for caching the -- intermediate results of a computation. -- --

Examples

-- -- Basic usage: -- --
--   >>> let expensiveDouble a = putStrLn ("Doubling " <> show a) >> pure (2 * a)
--   
--   >>> :{
--   mapAccumM (\cache a -> case lookup a cache of
--       Nothing -> expensiveDouble a >>= \double -> pure ((a, double):cache, double)
--       Just double -> pure (cache, double)
--       ) [] [1, 2, 3, 1, 2, 3]
--   :}
--   Doubling 1
--   Doubling 2
--   Doubling 3
--   ([(3,6),(2,4),(1,2)],[2,4,6,2,4,6])
--   
mapAccumM :: (Monad m, Traversable t) => (s -> a -> m (s, b)) -> s -> t a -> m (s, t b) -- | 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 :: 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 :: (Traversable t, Monoid m) => (a -> m) -> t a -> m 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 f => Data.Traversable.Traversable (Data.Semigroup.Internal.Alt f) instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Data.Monoid.Ap f) instance GHC.Ix.Ix i => Data.Traversable.Traversable (GHC.Arr.Array i) instance Data.Traversable.Traversable (Data.Functor.Const.Const m) instance Data.Traversable.Traversable Data.Ord.Down instance Data.Traversable.Traversable Data.Semigroup.Internal.Dual instance Data.Traversable.Traversable (Data.Either.Either a) instance Data.Traversable.Traversable Data.Monoid.First instance Data.Traversable.Traversable Data.Functor.Identity.Identity instance Data.Traversable.Traversable (GHC.Generics.K1 i c) instance Data.Traversable.Traversable Data.Monoid.Last instance Data.Traversable.Traversable [] instance Data.Traversable.Traversable f => Data.Traversable.Traversable (GHC.Generics.M1 i c f) instance Data.Traversable.Traversable GHC.Maybe.Maybe instance Data.Traversable.Traversable GHC.Base.NonEmpty instance Data.Traversable.Traversable GHC.Generics.Par1 instance Data.Traversable.Traversable Data.Semigroup.Internal.Product instance Data.Traversable.Traversable Data.Proxy.Proxy instance Data.Traversable.Traversable f => Data.Traversable.Traversable (GHC.Generics.Rec1 f) instance Data.Traversable.Traversable GHC.Tuple.Prim.Solo instance Data.Traversable.Traversable Data.Semigroup.Internal.Sum instance Data.Traversable.Traversable ((,) a) instance Data.Traversable.Traversable GHC.Generics.U1 instance Data.Traversable.Traversable GHC.Generics.UAddr instance Data.Traversable.Traversable GHC.Generics.UChar instance Data.Traversable.Traversable GHC.Generics.UDouble instance Data.Traversable.Traversable GHC.Generics.UFloat instance Data.Traversable.Traversable GHC.Generics.UInt instance Data.Traversable.Traversable GHC.Generics.UWord instance Data.Traversable.Traversable GHC.Generics.V1 instance Data.Traversable.Traversable Control.Applicative.ZipList -- | Operations on lists. module Data.List -- | (++) appends 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. -- --

Performance considerations

-- -- This function takes linear time in the number of elements of the -- first list. Thus it is better to associate repeated -- applications of (++) to the right (which is the default -- behaviour): xs ++ (ys ++ zs) or simply xs ++ ys ++ -- zs, but not (xs ++ ys) ++ zs. For the same reason -- concat = foldr (++) [] has -- linear performance, while foldl (++) [] is -- prone to quadratic slowdown -- --

Examples

-- --
--   >>> [1, 2, 3] ++ [4, 5, 6]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> [] ++ [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> [3, 2, 1] ++ []
--   [3,2,1]
--   
(++) :: [a] -> [a] -> [a] infixr 5 ++ -- | <math>. Extract the first element of a list, which must be -- non-empty. -- --
Examples
-- --
--   >>> head [1, 2, 3]
--   1
--   
-- --
--   >>> head [1..]
--   1
--   
-- --
--   >>> head []
--   *** Exception: Prelude.head: empty list
--   
-- | Warning: This is a partial function, it throws an error on empty -- lists. Use pattern matching or Data.List.uncons instead. Consider -- refactoring to use Data.List.NonEmpty. head :: HasCallStack => [a] -> a -- | <math>. Extract the last element of a list, which must be finite -- and non-empty. -- -- WARNING: This function is partial. Consider using unsnoc -- instead. -- --

Examples

-- --
--   >>> last [1, 2, 3]
--   3
--   
-- --
--   >>> last [1..]
--   * Hangs forever *
--   
-- --
--   >>> last []
--   *** Exception: Prelude.last: empty list
--   
last :: HasCallStack => [a] -> a -- | <math>. Extract the elements after the head of a list, which -- must be non-empty. -- --

Examples

-- --
--   >>> tail [1, 2, 3]
--   [2,3]
--   
-- --
--   >>> tail [1]
--   []
--   
-- --
--   >>> tail []
--   *** Exception: Prelude.tail: empty list
--   
-- | Warning: This is a partial function, it throws an error on empty -- lists. Replace it with drop 1, or use pattern matching or -- Data.List.uncons instead. Consider refactoring to use -- Data.List.NonEmpty. tail :: HasCallStack => [a] -> [a] -- | <math>. Return all the elements of a list except the last one. -- The list must be non-empty. -- -- WARNING: This function is partial. Consider using unsnoc -- instead. -- --

Examples

-- --
--   >>> init [1, 2, 3]
--   [1,2]
--   
-- --
--   >>> init [1]
--   []
--   
-- --
--   >>> init []
--   *** Exception: Prelude.init: empty list
--   
init :: HasCallStack => [a] -> [a] -- | <math>. Decompose a list into its head and tail. -- -- -- --

Examples

-- --
--   >>> uncons []
--   Nothing
--   
-- --
--   >>> uncons [1]
--   Just (1,[])
--   
-- --
--   >>> uncons [1, 2, 3]
--   Just (1,[2,3])
--   
uncons :: [a] -> Maybe (a, [a]) -- | <math>. Decompose a list into init and last. -- -- -- -- unsnoc is dual to uncons: for a finite list xs -- --
--   unsnoc xs = (\(hd, tl) -> (reverse tl, hd)) <$> uncons (reverse xs)
--   
-- --

Examples

-- --
--   >>> unsnoc []
--   Nothing
--   
-- --
--   >>> unsnoc [1]
--   Just ([],1)
--   
-- --
--   >>> unsnoc [1, 2, 3]
--   Just ([1,2],3)
--   
-- --

Laziness

-- --
--   >>> fst <$> unsnoc [undefined]
--   Just []
--   
-- --
--   >>> head . fst <$> unsnoc (1 : undefined)
--   Just *** Exception: Prelude.undefined
--   
-- --
--   >>> head . fst <$> unsnoc (1 : 2 : undefined)
--   Just 1
--   
unsnoc :: [a] -> Maybe ([a], a) -- | Construct a list from a single element. -- --

Examples

-- --
--   >>> singleton True
--   [True]
--   
-- --
--   >>> singleton [1, 2, 3]
--   [[1,2,3]]
--   
-- --
--   >>> singleton 'c'
--   "c"
--   
singleton :: a -> [a] -- | Test whether the structure is empty. The default implementation is -- Left-associative and lazy in both the initial element and the -- accumulator. Thus optimised for structures where the first element can -- be accessed in constant time. Structures where this is not the case -- should have a non-default implementation. -- --

Examples

-- -- Basic usage: -- --
--   >>> null []
--   True
--   
-- --
--   >>> null [1]
--   False
--   
-- -- null is expected to terminate even for infinite structures. The -- default implementation terminates provided the structure is bounded on -- the left (there is a leftmost element). -- --
--   >>> null [1..]
--   False
--   
null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation just counts elements starting with the -- leftmost. Instances for structures that can compute the element count -- faster than via element-by-element counting, should provide a -- specialised implementation. -- --

Examples

-- -- Basic usage: -- --
--   >>> length []
--   0
--   
-- --
--   >>> length ['a', 'b', 'c']
--   3
--   
--   >>> length [1..]
--   * Hangs forever *
--   
length :: Foldable t => t a -> Int -- | <math>. 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, ...]
--   
-- -- this means that map id == id -- --

Examples

-- --
--   >>> map (+1) [1, 2, 3]
--   [2,3,4]
--   
-- --
--   >>> map id [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> map (\n -> 3 * n + 1) [1, 2, 3]
--   [4,7,10]
--   
map :: (a -> b) -> [a] -> [b] -- | <math>. reverse xs returns the elements of -- xs in reverse order. xs must be finite. -- --

Laziness

-- -- reverse is lazy in its elements. -- --
--   >>> head (reverse [undefined, 1])
--   1
--   
-- --
--   >>> reverse (1 : 2 : undefined)
--   *** Exception: Prelude.undefined
--   
-- --

Examples

-- --
--   >>> reverse []
--   []
--   
-- --
--   >>> reverse [42]
--   [42]
--   
-- --
--   >>> reverse [2,5,7]
--   [7,5,2]
--   
-- --
--   >>> reverse [1..]
--   * Hangs forever *
--   
reverse :: [a] -> [a] -- | <math>. The intersperse function takes an element and a -- list and `intersperses' that element between the elements of the list. -- --

Laziness

-- -- intersperse has the following properties -- --
--   >>> take 1 (intersperse undefined ('a' : undefined))
--   "a"
--   
-- --
--   >>> take 2 (intersperse ',' ('a' : undefined))
--   "a*** Exception: Prelude.undefined
--   
-- --

Examples

-- --
--   >>> intersperse ',' "abcde"
--   "a,b,c,d,e"
--   
-- --
--   >>> intersperse 1 [3, 4, 5]
--   [3,1,4,1,5]
--   
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. -- --

Laziness

-- -- intercalate has the following properties: -- --
--   >>> take 5 (intercalate undefined ("Lorem" : undefined))
--   "Lorem"
--   
-- --
--   >>> take 6 (intercalate ", " ("Lorem" : undefined))
--   "Lorem*** Exception: Prelude.undefined
--   
-- --

Examples

-- --
--   >>> intercalate ", " ["Lorem", "ipsum", "dolor"]
--   "Lorem, ipsum, dolor"
--   
-- --
--   >>> intercalate [0, 1] [[2, 3], [4, 5, 6], []]
--   [2,3,0,1,4,5,6,0,1]
--   
-- --
--   >>> intercalate [1, 2, 3] [[], []]
--   [1,2,3]
--   
intercalate :: [a] -> [[a]] -> [a] -- | The transpose function transposes the rows and columns of its -- argument. -- --

Laziness

-- -- transpose is lazy in its elements -- --
--   >>> take 1 (transpose ['a' : undefined, 'b' : undefined])
--   ["ab"]
--   
-- --

Examples

-- --
--   >>> 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]]
--   
-- -- For this reason the outer list must be finite; otherwise -- transpose hangs: -- --
--   >>> transpose (repeat [])
--   * Hangs forever *
--   
transpose :: [[a]] -> [[a]] -- | The subsequences function returns the list of all subsequences -- of the argument. -- --

Laziness

-- -- subsequences does not look ahead unless it must: -- --
--   >>> take 1 (subsequences undefined)
--   [[]]
--   
--   >>> take 2 (subsequences ('a' : undefined))
--   ["","a"]
--   
-- --

Examples

-- --
--   >>> subsequences "abc"
--   ["","a","b","ab","c","ac","bc","abc"]
--   
-- -- This function is productive on infinite inputs: -- --
--   >>> take 8 $ subsequences ['a'..]
--   ["","a","b","ab","c","ac","bc","abc"]
--   
subsequences :: [a] -> [[a]] -- | The permutations function returns the list of all permutations -- of the argument. -- -- Note that the order of permutations is not lexicographic. It satisfies -- the following property: -- --
--   map (take n) (take (product [1..n]) (permutations ([1..n] ++ undefined))) == permutations [1..n]
--   
-- --

Laziness

-- -- The permutations function is maximally lazy: for each -- n, the value of permutations xs starts with -- those permutations that permute take n xs and keep -- drop n xs. -- --

Examples

-- --
--   >>> permutations "abc"
--   ["abc","bac","cba","bca","cab","acb"]
--   
-- --
--   >>> permutations [1, 2]
--   [[1,2],[2,1]]
--   
-- --
--   >>> permutations []
--   [[]]
--   
-- -- This function is productive on infinite inputs: -- --
--   >>> take 6 $ map (take 3) $ permutations ['a'..]
--   ["abc","bac","cba","bca","cab","acb"]
--   
permutations :: [a] -> [[a]] -- | Left-associative fold of a structure, lazy in the accumulator. This is -- rarely what you want, but can work well for structures with efficient -- right-to-left sequencing and an operator that is lazy in its left -- argument. -- -- 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. Like all left-associative folds, -- foldl will diverge if given an infinite list. -- -- If you want an efficient strict left-fold, you probably want to use -- foldl' instead of foldl. The reason for this is that the -- 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
--   
-- --

Examples

-- -- The first example is a strict fold, which in practice is best -- performed with foldl'. -- --
--   >>> foldl (+) 42 [1,2,3,4]
--   52
--   
-- -- Though the result below is lazy, the input is reversed before -- prepending it to the initial accumulator, so corecursion begins only -- after traversing the entire input string. -- --
--   >>> foldl (\acc c -> c : acc) "abcd" "efgh"
--   "hgfeabcd"
--   
-- -- A left fold of a structure that is infinite on the right cannot -- terminate, even when for any finite input the fold just returns the -- initial accumulator: -- --
--   >>> foldl (\a _ -> a) 0 $ repeat 1
--   * Hangs forever *
--   
-- -- WARNING: When it comes to lists, you always want to use either -- foldl' or foldr instead. 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 structure to a single strict result (e.g. sum). -- -- 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. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. -- --
--   foldl1 f = foldl1 f . toList
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> foldl1 (+) [1..4]
--   10
--   
-- --
--   >>> foldl1 (+) []
--   *** Exception: Prelude.foldl1: empty list
--   
-- --
--   >>> foldl1 (+) Nothing
--   *** Exception: foldl1: empty structure
--   
-- --
--   >>> foldl1 (-) [1..4]
--   -8
--   
-- --
--   >>> foldl1 (&&) [True, False, True, True]
--   False
--   
-- --
--   >>> foldl1 (||) [False, False, True, True]
--   True
--   
-- --
--   >>> foldl1 (+) [1..]
--   * Hangs forever *
--   
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a -- | A strict version of foldl1. foldl1' :: HasCallStack => (a -> a -> a) -> [a] -> a -- | Right-associative fold of a structure, lazy in the accumulator. -- -- 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, given an -- operator lazy in its right argument, foldr can produce a -- terminating expression from an unbounded list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldr f z = foldr f z . toList
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> foldr (||) False [False, True, False]
--   True
--   
-- --
--   >>> foldr (||) False []
--   False
--   
-- --
--   >>> foldr (\c acc -> acc ++ [c]) "foo" ['a', 'b', 'c', 'd']
--   "foodcba"
--   
-- --
Infinite structures
-- -- ⚠️ Applying foldr to infinite structures usually doesn't -- terminate. -- -- It may still terminate under one of the following conditions: -- -- -- --
Short-circuiting
-- -- (||) short-circuits on True values, so the -- following terminates because there is a True value finitely far -- from the left side: -- --
--   >>> foldr (||) False (True : repeat False)
--   True
--   
-- -- But the following doesn't terminate: -- --
--   >>> foldr (||) False (repeat False ++ [True])
--   * Hangs forever *
--   
-- --
Laziness in the second argument
-- -- Applying foldr to infinite structures terminates when the -- operator is lazy in its second argument (the initial accumulator is -- never used in this case, and so could be left undefined, but -- [] is more clear): -- --
--   >>> take 5 $ foldr (\i acc -> i : fmap (+3) acc) [] (repeat 1)
--   [1,4,7,10,13]
--   
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. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. -- --

Examples

-- -- Basic usage: -- --
--   >>> foldr1 (+) [1..4]
--   10
--   
-- --
--   >>> foldr1 (+) []
--   Exception: Prelude.foldr1: empty list
--   
-- --
--   >>> foldr1 (+) Nothing
--   *** Exception: foldr1: empty structure
--   
-- --
--   >>> foldr1 (-) [1..4]
--   -2
--   
-- --
--   >>> foldr1 (&&) [True, False, True, True]
--   False
--   
-- --
--   >>> foldr1 (||) [False, False, True, True]
--   True
--   
-- --
--   >>> foldr1 (+) [1..]
--   * Hangs forever *
--   
foldr1 :: Foldable t => (a -> a -> a) -> t a -> a -- | The concatenation of all the elements of a container of lists. -- --

Examples

-- -- Basic usage: -- --
--   >>> concat (Just [1, 2, 3])
--   [1,2,3]
--   
-- --
--   >>> concat (Left 42)
--   []
--   
-- --
--   >>> concat [[1, 2, 3], [4, 5], [6], []]
--   [1,2,3,4,5,6]
--   
concat :: Foldable t => t [a] -> [a] -- | Map a function over all the elements of a container and concatenate -- the resulting lists. -- --

Examples

-- -- Basic usage: -- --
--   >>> concatMap (take 3) [[1..], [10..], [100..], [1000..]]
--   [1,2,3,10,11,12,100,101,102,1000,1001,1002]
--   
-- --
--   >>> concatMap (take 3) (Just [1..])
--   [1,2,3]
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> and []
--   True
--   
-- --
--   >>> and [True]
--   True
--   
-- --
--   >>> and [False]
--   False
--   
-- --
--   >>> and [True, True, False]
--   False
--   
-- --
--   >>> and (False : repeat True) -- Infinite list [False,True,True,True,...
--   False
--   
-- --
--   >>> and (repeat True)
--   * Hangs forever *
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> or []
--   False
--   
-- --
--   >>> or [True]
--   True
--   
-- --
--   >>> or [False]
--   False
--   
-- --
--   >>> or [True, True, False]
--   True
--   
-- --
--   >>> or (True : repeat False) -- Infinite list [True,False,False,False,...
--   True
--   
-- --
--   >>> or (repeat False)
--   * Hangs forever *
--   
or :: Foldable t => t Bool -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. -- --

Examples

-- -- Basic usage: -- --
--   >>> any (> 3) []
--   False
--   
-- --
--   >>> any (> 3) [1,2]
--   False
--   
-- --
--   >>> any (> 3) [1,2,3,4,5]
--   True
--   
-- --
--   >>> any (> 3) [1..]
--   True
--   
-- --
--   >>> any (> 3) [0, -1..]
--   * Hangs forever *
--   
any :: Foldable t => (a -> Bool) -> t a -> Bool -- | Determines whether all elements of the structure satisfy the -- predicate. -- --

Examples

-- -- Basic usage: -- --
--   >>> all (> 3) []
--   True
--   
-- --
--   >>> all (> 3) [1,2]
--   False
--   
-- --
--   >>> all (> 3) [1,2,3,4,5]
--   False
--   
-- --
--   >>> all (> 3) [1..]
--   False
--   
-- --
--   >>> all (> 3) [4..]
--   * Hangs forever *
--   
all :: Foldable t => (a -> Bool) -> t a -> Bool -- | The sum function computes the sum of the numbers of a -- structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> sum []
--   0
--   
-- --
--   >>> sum [42]
--   42
--   
-- --
--   >>> sum [1..10]
--   55
--   
-- --
--   >>> sum [4.1, 2.0, 1.7]
--   7.8
--   
-- --
--   >>> sum [1..]
--   * Hangs forever *
--   
sum :: (Foldable t, Num a) => t a -> a -- | The product function computes the product of the numbers of a -- structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> product []
--   1
--   
-- --
--   >>> product [42]
--   42
--   
-- --
--   >>> product [1..10]
--   3628800
--   
-- --
--   >>> product [4.1, 2.0, 1.7]
--   13.939999999999998
--   
-- --
--   >>> product [1..]
--   * Hangs forever *
--   
product :: (Foldable t, Num a) => t a -> a -- | The largest element of a non-empty structure. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. A structure that supports random access -- and maintains its elements in order should provide a specialised -- implementation to return the maximum in faster than linear time. -- --

Examples

-- -- Basic usage: -- --
--   >>> maximum [1..10]
--   10
--   
-- --
--   >>> maximum []
--   *** Exception: Prelude.maximum: empty list
--   
-- --
--   >>> maximum Nothing
--   *** Exception: maximum: empty structure
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. maximum :: (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. A structure that supports random access -- and maintains its elements in order should provide a specialised -- implementation to return the minimum in faster than linear time. -- --

Examples

-- -- Basic usage: -- --
--   >>> minimum [1..10]
--   1
--   
-- --
--   >>> minimum []
--   *** Exception: Prelude.minimum: empty list
--   
-- --
--   >>> minimum Nothing
--   *** Exception: minimum: empty structure
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. minimum :: (Foldable t, Ord a) => t a -> a -- | <math>. 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
--   
-- --

Examples

-- --
--   >>> scanl (+) 0 [1..4]
--   [0,1,3,6,10]
--   
-- --
--   >>> scanl (+) 42 []
--   [42]
--   
-- --
--   >>> scanl (-) 100 [1..4]
--   [100,99,97,94,90]
--   
-- --
--   >>> scanl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   ["foo","afoo","bafoo","cbafoo","dcbafoo"]
--   
-- --
--   >>> take 10 (scanl (+) 0 [1..])
--   [0,1,3,6,10,15,21,28,36,45]
--   
-- --
--   >>> take 1 (scanl undefined 'a' undefined)
--   "a"
--   
scanl :: (b -> a -> b) -> b -> [a] -> [b] -- | <math>. A strict version of scanl. scanl' :: (b -> a -> b) -> b -> [a] -> [b] -- | <math>. scanl1 is a variant of scanl that has no -- starting value argument: -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
-- --

Examples

-- --
--   >>> scanl1 (+) [1..4]
--   [1,3,6,10]
--   
-- --
--   >>> scanl1 (+) []
--   []
--   
-- --
--   >>> scanl1 (-) [1..4]
--   [1,-1,-4,-8]
--   
-- --
--   >>> scanl1 (&&) [True, False, True, True]
--   [True,False,False,False]
--   
-- --
--   >>> scanl1 (||) [False, False, True, True]
--   [False,False,True,True]
--   
-- --
--   >>> take 10 (scanl1 (+) [1..])
--   [1,3,6,10,15,21,28,36,45,55]
--   
-- --
--   >>> take 1 (scanl1 undefined ('a' : undefined))
--   "a"
--   
scanl1 :: (a -> a -> a) -> [a] -> [a] -- | <math>. scanr is the right-to-left dual of scanl. -- Note that the order of parameters on the accumulating function are -- reversed compared to scanl. Also note that -- --
--   head (scanr f z xs) == foldr f z xs.
--   
-- --

Examples

-- --
--   >>> scanr (+) 0 [1..4]
--   [10,9,7,4,0]
--   
-- --
--   >>> scanr (+) 42 []
--   [42]
--   
-- --
--   >>> scanr (-) 100 [1..4]
--   [98,-97,99,-96,100]
--   
-- --
--   >>> scanr (\nextChar reversedString -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   ["abcdfoo","bcdfoo","cdfoo","dfoo","foo"]
--   
-- --
--   >>> force $ scanr (+) 0 [1..]
--   *** Exception: stack overflow
--   
scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | <math>. scanr1 is a variant of scanr that has no -- starting value argument. -- --

Examples

-- --
--   >>> scanr1 (+) [1..4]
--   [10,9,7,4]
--   
-- --
--   >>> scanr1 (+) []
--   []
--   
-- --
--   >>> scanr1 (-) [1..4]
--   [-2,3,-1,4]
--   
-- --
--   >>> scanr1 (&&) [True, False, True, True]
--   [False,False,True,True]
--   
-- --
--   >>> scanr1 (||) [True, True, False, False]
--   [True,True,False,False]
--   
-- --
--   >>> force $ scanr1 (+) [1..]
--   *** Exception: stack overflow
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> mapAccumL (\a b -> (a + b, a)) 0 [1..10]
--   (55,[0,1,3,6,10,15,21,28,36,45])
--   
-- --
--   >>> mapAccumL (\a b -> (a <> show b, a)) "0" [1..5]
--   ("012345",["0","01","012","0123","01234"])
--   
mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) -- | 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. -- --

Examples

-- -- Basic usage: -- --
--   >>> mapAccumR (\a b -> (a + b, a)) 0 [1..10]
--   (55,[54,52,49,45,40,34,27,19,10,0])
--   
-- --
--   >>> mapAccumR (\a b -> (a <> show b, a)) "0" [1..5]
--   ("054321",["05432","0543","054","05","0"])
--   
mapAccumR :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) -- | iterate f x returns an infinite list of repeated -- applications of f to x: -- --
--   iterate f x == [x, f x, f (f x), ...]
--   
-- --

Laziness

-- -- Note that iterate is lazy, potentially leading to thunk -- build-up if the consumer doesn't force each iterate. See -- iterate' for a strict variant of this function. -- --
--   >>> take 1 $ iterate undefined 42
--   [42]
--   
-- --

Examples

-- --
--   >>> take 10 $ iterate not True
--   [True,False,True,False,True,False,True,False,True,False]
--   
-- --
--   >>> take 10 $ iterate (+3) 42
--   [42,45,48,51,54,57,60,63,66,69]
--   
-- -- iterate id == repeat: -- --
--   >>> take 10 $ iterate id 1
--   [1,1,1,1,1,1,1,1,1,1]
--   
iterate :: (a -> a) -> a -> [a] -- | iterate' is the strict version of iterate. -- -- It forces the result of each application of the function to weak head -- normal form (WHNF) before proceeding. -- --
--   >>> take 1 $ iterate' undefined 42
--   *** Exception: Prelude.undefined
--   
iterate' :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. -- --

Examples

-- --
--   >>> take 10 $ repeat 17
--   [17,17,17,17,17,17,17,17,17, 17]
--   
-- --
--   >>> repeat undefined
--   [*** Exception: Prelude.undefined
--   
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. -- --

Examples

-- --
--   >>> replicate 0 True
--   []
--   
-- --
--   >>> replicate (-1) True
--   []
--   
-- --
--   >>> replicate 4 True
--   [True,True,True,True]
--   
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. -- --

Examples

-- --
--   >>> cycle []
--   *** Exception: Prelude.cycle: empty list
--   
-- --
--   >>> take 10 (cycle [42])
--   [42,42,42,42,42,42,42,42,42,42]
--   
-- --
--   >>> take 10 (cycle [2, 5, 7])
--   [2,5,7,2,5,7,2,5,7,2]
--   
-- --
--   >>> take 1 (cycle (42 : undefined))
--   [42]
--   
cycle :: HasCallStack => [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
--   
-- --

Laziness

-- --
--   >>> take 1 (unfoldr (\x -> Just (x, undefined)) 'a')
--   "a"
--   
-- --

Examples

-- --
--   >>> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
--   [10,9,8,7,6,5,4,3,2,1]
--   
-- --
--   >>> take 10 $ unfoldr (\(x, y) -> Just (x, (y, x + y))) (0, 1)
--   [0,1,1,2,3,5,8,13,21,54]
--   
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. -- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. -- --

Laziness

-- --
--   >>> take 0 undefined
--   []
--   
--   >>> take 2 (1 : 2 : undefined)
--   [1,2]
--   
-- --

Examples

-- --
--   >>> 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]
--   []
--   
take :: Int -> [a] -> [a] -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n >= length -- xs. -- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. -- --

Examples

-- --
--   >>> 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]
--   
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 is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. -- --

Laziness

-- -- It is equivalent to (take n xs, drop n xs) -- unless n is _|_: splitAt _|_ xs = _|_, not -- (_|_, _|_)). -- -- The first component of the tuple is produced lazily: -- --
--   >>> fst (splitAt 0 undefined)
--   []
--   
-- --
--   >>> take 1 (fst (splitAt 10 (1 : undefined)))
--   [1]
--   
-- --

Examples

-- --
--   >>> 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])
--   
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. -- --

Laziness

-- --
--   >>> takeWhile (const False) undefined
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> takeWhile (const False) (undefined : undefined)
--   []
--   
-- --
--   >>> take 1 (takeWhile (const True) (1 : undefined))
--   [1]
--   
-- --

Examples

-- --
--   >>> 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. -- --

Examples

-- --
--   >>> 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. -- --

Laziness

-- -- This function is lazy in spine, but strict in elements, which makes it -- different from reverse . dropWhile p -- . reverse, which is strict in spine, but lazy in -- elements. For instance: -- --
--   >>> take 1 (dropWhileEnd (< 0) (1 : undefined))
--   [1]
--   
-- --
--   >>> take 1 (reverse $ dropWhile (< 0) $ reverse (1 : undefined))
--   *** Exception: Prelude.undefined
--   
-- -- but on the other hand -- --
--   >>> last (dropWhileEnd (< 0) [undefined, 1])
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> last (reverse $ dropWhile (< 0) $ reverse [undefined, 1])
--   1
--   
-- --

Examples

-- --
--   >>> dropWhileEnd isSpace "foo\n"
--   "foo"
--   
-- --
--   >>> dropWhileEnd isSpace "foo bar"
--   "foo bar"
--   
--   >>> dropWhileEnd (> 10) [1..20]
--   [1,2,3,4,5,6,7,8,9,10]
--   
dropWhileEnd :: (a -> Bool) -> [a] -> [a] -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is the longest prefix (possibly -- empty) of xs of elements that satisfy p and second -- element is the remainder of the list: -- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs), even if p is _|_. -- --

Laziness

-- --
--   >>> span undefined []
--   ([],[])
--   
--   >>> fst (span (const False) undefined)
--   *** Exception: Prelude.undefined
--   
--   >>> fst (span (const False) (undefined : undefined))
--   []
--   
--   >>> take 1 (fst (span (const True) (1 : undefined)))
--   [1]
--   
-- -- span produces the first component of the tuple lazily: -- --
--   >>> take 10 (fst (span (const True) [1..]))
--   [1,2,3,4,5,6,7,8,9,10]
--   
-- --

Examples

-- --
--   >>> 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 :: (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 p is equivalent to span (not . -- p) and consequently to (takeWhile (not . p) xs, -- dropWhile (not . p) xs), even if p is -- _|_. -- --

Laziness

-- --
--   >>> break undefined []
--   ([],[])
--   
-- --
--   >>> fst (break (const True) undefined)
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> fst (break (const True) (undefined : undefined))
--   []
--   
-- --
--   >>> take 1 (fst (break (const False) (1 : undefined)))
--   [1]
--   
-- -- break produces the first component of the tuple lazily: -- --
--   >>> take 10 (fst (break (const False) [1..]))
--   [1,2,3,4,5,6,7,8,9,10]
--   
-- --

Examples

-- --
--   >>> 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 :: (a -> Bool) -> [a] -> ([a], [a]) -- | <math>. 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. -- --
Examples
-- --
--   >>> 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 is non-empty and all elements are -- equal to the first one. -- -- group is a special case of groupBy, which allows the -- programmer to supply their own equality test. -- -- It's often preferable to use Data.List.NonEmpty.group, -- which provides type-level guarantees of non-emptiness of inner lists. -- --

Examples

-- --
--   >>> group "Mississippi"
--   ["M","i","ss","i","ss","i","pp","i"]
--   
-- --
--   >>> group [1, 1, 1, 2, 2, 3, 4, 5, 5]
--   [[1,1,1],[2,2],[3],[4],[5,5]]
--   
group :: Eq a => [a] -> [[a]] -- | The inits function returns all initial segments of the -- argument, shortest first. -- -- inits is semantically equivalent to map -- reverse . scanl (flip (:)) [], but under the -- hood uses a queue to amortize costs of reverse. -- --

Laziness

-- -- Note that inits has the following strictness property: -- inits (xs ++ _|_) = inits xs ++ _|_ -- -- In particular, inits _|_ = [] : _|_ -- --

Examples

-- --
--   >>> inits "abc"
--   ["","a","ab","abc"]
--   
-- --
--   >>> inits []
--   [[]]
--   
-- -- inits is productive on infinite lists: -- --
--   >>> take 5 $ inits [1..]
--   [[],[1],[1,2],[1,2,3],[1,2,3,4]]
--   
inits :: [a] -> [[a]] -- | <math>. The tails function returns all final segments of -- the argument, longest first. -- --

Laziness

-- -- Note that tails has the following strictness property: -- tails _|_ = _|_ : _|_ -- --
--   >>> tails undefined
--   [*** Exception: Prelude.undefined
--   
-- --
--   >>> drop 1 (tails [undefined, 1, 2])
--   [[1, 2], [2], []]
--   
-- --

Examples

-- --
--   >>> tails "abc"
--   ["abc","bc","c",""]
--   
-- --
--   >>> tails [1, 2, 3]
--   [[1,2,3],[2,3],[3],[]]
--   
-- --
--   >>> tails []
--   [[]]
--   
tails :: [a] -> [[a]] -- | <math>. The isPrefixOf function takes two lists and -- returns True iff the first list is a prefix of the second. -- --

Examples

-- --
--   >>> "Hello" `isPrefixOf` "Hello World!"
--   True
--   
-- --
--   >>> "Hello" `isPrefixOf` "Wello Horld!"
--   False
--   
-- -- For the result to be True, the first list must be finite; -- False, however, results from any mismatch: -- --
--   >>> [0..] `isPrefixOf` [1..]
--   False
--   
-- --
--   >>> [0..] `isPrefixOf` [0..99]
--   False
--   
-- --
--   >>> [0..99] `isPrefixOf` [0..]
--   True
--   
-- --
--   >>> [0..] `isPrefixOf` [0..]
--   * Hangs forever *
--   
-- -- isPrefixOf shortcuts when the first argument is empty: -- --
--   >>> isPrefixOf [] undefined
--   True
--   
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. -- --

Examples

-- --
--   >>> "ld!" `isSuffixOf` "Hello World!"
--   True
--   
-- --
--   >>> "World" `isSuffixOf` "Hello World!"
--   False
--   
-- -- The second list must be finite; however the first list may be -- infinite: -- --
--   >>> [0..] `isSuffixOf` [0..99]
--   False
--   
-- --
--   >>> [0..99] `isSuffixOf` [0..]
--   * Hangs forever *
--   
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. -- --

Examples

-- --
--   >>> isInfixOf "Haskell" "I really like Haskell."
--   True
--   
-- --
--   >>> isInfixOf "Ial" "I really like Haskell."
--   False
--   
-- -- For the result to be True, the first list must be finite; for -- the result to be False, the second list must be finite: -- --
--   >>> [20..50] `isInfixOf` [0..]
--   True
--   
-- --
--   >>> [0..] `isInfixOf` [20..50]
--   False
--   
-- --
--   >>> [0..] `isInfixOf` [0..]
--   * Hangs forever *
--   
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 x -- `elem` (subsequences y). -- -- Note: isSubsequenceOf is often used in infix form. -- --

Examples

-- --
--   >>> "GHC" `isSubsequenceOf` "The Glorious Haskell Compiler"
--   True
--   
-- --
--   >>> ['a','d'..'z'] `isSubsequenceOf` ['a'..'z']
--   True
--   
-- --
--   >>> [1..10] `isSubsequenceOf` [10,9..0]
--   False
--   
-- -- For the result to be True, the first list must be finite; for -- the result to be False, the second list must be finite: -- --
--   >>> [0,2..10] `isSubsequenceOf` [0..]
--   True
--   
-- --
--   >>> [0..] `isSubsequenceOf` [0,2..10]
--   False
--   
-- --
--   >>> [0,2..] `isSubsequenceOf` [0..]
--   * Hangs forever*
--   
isSubsequenceOf :: Eq a => [a] -> [a] -> Bool -- | Does the element occur in the structure? -- -- Note: elem is often used in infix form. -- --

Examples

-- -- Basic usage: -- --
--   >>> 3 `elem` []
--   False
--   
-- --
--   >>> 3 `elem` [1,2]
--   False
--   
-- --
--   >>> 3 `elem` [1,2,3,4,5]
--   True
--   
-- -- For infinite structures, the default implementation of elem -- terminates if the sought-after value exists at a finite distance from -- the left side of the structure: -- --
--   >>> 3 `elem` [1..]
--   True
--   
-- --
--   >>> 3 `elem` ([4..] ++ [3])
--   * Hangs forever *
--   
elem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `elem` -- | notElem is the negation of elem. -- --

Examples

-- -- Basic usage: -- --
--   >>> 3 `notElem` []
--   True
--   
-- --
--   >>> 3 `notElem` [1,2]
--   True
--   
-- --
--   >>> 3 `notElem` [1,2,3,4,5]
--   False
--   
-- -- For infinite structures, notElem terminates if the value exists -- at a finite distance from the left side of the structure: -- --
--   >>> 3 `notElem` [1..]
--   False
--   
-- --
--   >>> 3 `notElem` ([4..] ++ [3])
--   * Hangs forever *
--   
notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `notElem` -- | <math>. lookup key assocs looks up a key in an -- association list. For the result to be Nothing, the list must -- be finite. -- --

Examples

-- --
--   >>> lookup 2 []
--   Nothing
--   
-- --
--   >>> lookup 2 [(1, "first")]
--   Nothing
--   
-- --
--   >>> lookup 2 [(1, "first"), (2, "second"), (3, "third")]
--   Just "second"
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> find (> 42) [0, 5..]
--   Just 45
--   
-- --
--   >>> find (> 12) [1..7]
--   Nothing
--   
find :: Foldable t => (a -> Bool) -> t a -> Maybe a -- | <math>. 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]
--   
-- --

Examples

-- --
--   >>> filter odd [1, 2, 3]
--   [1,3]
--   
-- --
--   >>> filter (\l -> length l > 3) ["Hello", ", ", "World", "!"]
--   ["Hello","World"]
--   
-- --
--   >>> filter (/= 3) [1, 2, 3, 4, 3, 2, 1]
--   [1,2,4,2,1]
--   
filter :: (a -> Bool) -> [a] -> [a] -- | The partition function takes a predicate and 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)
--   
-- --

Examples

-- --
--   >>> partition (`elem` "aeiou") "Hello World!"
--   ("eoo","Hll Wrld!")
--   
-- --
--   >>> partition even [1..10]
--   ([2,4,6,8,10],[1,3,5,7,9])
--   
-- --
--   >>> partition (< 5) [1..10]
--   ([1,2,3,4],[5,6,7,8,9,10])
--   
partition :: (a -> Bool) -> [a] -> ([a], [a]) -- | List index (subscript) operator, starting from 0. Returns -- Nothing if the index is out of bounds -- -- This is the total variant of the partial !! operator. -- -- WARNING: This function takes linear time in the index. -- --

Examples

-- --
--   >>> ['a', 'b', 'c'] !? 0
--   Just 'a'
--   
-- --
--   >>> ['a', 'b', 'c'] !? 2
--   Just 'c'
--   
-- --
--   >>> ['a', 'b', 'c'] !? 3
--   Nothing
--   
-- --
--   >>> ['a', 'b', 'c'] !? (-1)
--   Nothing
--   
(!?) :: [a] -> Int -> Maybe a infixl 9 !? -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. -- -- WARNING: This function is partial, and should only be used if you are -- sure that the indexing will not fail. Otherwise, use !?. -- -- WARNING: This function takes linear time in the index. -- --

Examples

-- --
--   >>> ['a', 'b', 'c'] !! 0
--   'a'
--   
-- --
--   >>> ['a', 'b', 'c'] !! 2
--   'c'
--   
-- --
--   >>> ['a', 'b', 'c'] !! 3
--   *** Exception: Prelude.!!: index too large
--   
-- --
--   >>> ['a', 'b', 'c'] !! (-1)
--   *** Exception: Prelude.!!: negative index
--   
(!!) :: HasCallStack => [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. For the result to be -- Nothing, the list must be finite. -- --

Examples

-- --
--   >>> elemIndex 4 [0..]
--   Just 4
--   
-- --
--   >>> elemIndex 'o' "haskell"
--   Nothing
--   
-- --
--   >>> elemIndex 0 [1..]
--   * hangs forever *
--   
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. -- --

Examples

-- --
--   >>> elemIndices 'o' "Hello World"
--   [4,7]
--   
-- --
--   >>> elemIndices 1 [1, 2, 3, 1, 2, 3]
--   [0,3]
--   
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. For the result to be -- Nothing, the list must be finite. -- --

Examples

-- --
--   >>> findIndex isSpace "Hello World!"
--   Just 5
--   
-- --
--   >>> findIndex odd [0, 2, 4, 6]
--   Nothing
--   
-- --
--   >>> findIndex even [1..]
--   Just 1
--   
-- --
--   >>> findIndex odd [0, 2 ..]
--   * hangs forever *
--   
findIndex :: (a -> Bool) -> [a] -> Maybe Int -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. -- --

Examples

-- --
--   >>> findIndices (`elem` "aeiou") "Hello World!"
--   [1,4,7]
--   
-- --
--   >>> findIndices (\l -> length l > 3) ["a", "bcde", "fgh", "ijklmnop"]
--   [1,3]
--   
findIndices :: (a -> Bool) -> [a] -> [Int] -- | <math>. zip takes two lists and returns a list of -- corresponding pairs. -- -- zip is right-lazy: -- --
--   >>> zip [] undefined
--   []
--   
--   >>> zip undefined []
--   *** Exception: Prelude.undefined
--   ...
--   
-- -- zip is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. -- --

Examples

-- --
--   >>> zip [1, 2, 3] ['a', 'b', 'c']
--   [(1,'a'),(2,'b'),(3,'c')]
--   
-- -- If one input list is shorter than the other, excess elements of the -- longer list are discarded, even if one of the lists is infinite: -- --
--   >>> zip [1] ['a', 'b']
--   [(1,'a')]
--   
-- --
--   >>> zip [1, 2] ['a']
--   [(1,'a')]
--   
-- --
--   >>> zip [] [1..]
--   []
--   
-- --
--   >>> zip [1..] []
--   []
--   
zip :: [a] -> [b] -> [(a, b)] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. It is capable of list fusion, but it is restricted to -- its first list argument and its resulting list. zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] -- | The zip4 function takes four lists and returns a list of -- quadruples, analogous to zip. It is capable of list fusion, but -- it is restricted to its first list argument and its resulting list. 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. It is capable of list fusion, -- but it is restricted to its first list argument and its resulting -- list. 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. It is capable of list fusion, but -- it is restricted to its first list argument and its resulting list. 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. It is capable of list fusion, -- but it is restricted to its first list argument and its resulting -- list. zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)] -- | <math>. zipWith generalises zip by zipping with -- the function given as the first argument, instead of a tupling -- function. -- --
--   zipWith (,) xs ys == zip xs ys
--   zipWith f [x1,x2,x3..] [y1,y2,y3..] == [f x1 y1, f x2 y2, f x3 y3..]
--   
-- -- zipWith is right-lazy: -- --
--   >>> let f = undefined
--   
--   >>> zipWith f [] undefined
--   []
--   
-- -- zipWith is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. -- --

Examples

-- -- zipWith (+) can be applied to two lists to -- produce the list of corresponding sums: -- --
--   >>> zipWith (+) [1, 2, 3] [4, 5, 6]
--   [5,7,9]
--   
-- --
--   >>> zipWith (++) ["hello ", "foo"] ["world!", "bar"]
--   ["hello world!","foobar"]
--   
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | <math>. The zipWith3 function takes a function which -- combines three elements, as well as three lists and returns a list of -- the function applied to corresponding elements, analogous to -- zipWith. It is capable of list fusion, but it is restricted to -- its first list argument and its resulting list. -- --
--   zipWith3 (,,) xs ys zs == zip3 xs ys zs
--   zipWith3 f [x1,x2,x3..] [y1,y2,y3..] [z1,z2,z3..] == [f x1 y1 z1, f x2 y2 z2, f x3 y3 z3..]
--   
-- --

Examples

-- --
--   >>> zipWith3 (\x y z -> [x, y, z]) "123" "abc" "xyz"
--   ["1ax","2by","3cz"]
--   
-- --
--   >>> zipWith3 (\x y z -> (x * y) + z) [1, 2, 3] [4, 5, 6] [7, 8, 9]
--   [11,18,27]
--   
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. It is capable of list -- fusion, but it is restricted to its first list argument and its -- resulting list. 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. It is capable of list -- fusion, but it is restricted to its first list argument and its -- resulting list. 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. It is capable of list -- fusion, but it is restricted to its first list argument and its -- resulting list. 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. It is capable of -- list fusion, but it is restricted to its first list argument and its -- resulting list. 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. -- --

Examples

-- --
--   >>> unzip []
--   ([],[])
--   
-- --
--   >>> unzip [(1, 'a'), (2, 'b')]
--   ([1,2],"ab")
--   
unzip :: [(a, b)] -> ([a], [b]) -- | The unzip3 function takes a list of triples and returns three -- lists of the respective components, analogous to unzip. -- --

Examples

-- --
--   >>> unzip3 []
--   ([],[],[])
--   
-- --
--   >>> unzip3 [(1, 'a', True), (2, 'b', False)]
--   ([1,2],"ab",[True,False])
--   
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]) -- | Splits the argument into a list of lines stripped of their -- terminating \n characters. The \n terminator is -- optional in a final non-empty line of the argument string. -- -- When the argument string is empty, or ends in a \n character, -- it can be recovered by passing the result of lines to the -- unlines function. Otherwise, unlines appends the missing -- terminating \n. This makes unlines . lines -- idempotent: -- --
--   (unlines . lines) . (unlines . lines) = (unlines . lines)
--   
-- --

Examples

-- --
--   >>> lines ""           -- empty input contains no lines
--   []
--   
-- --
--   >>> lines "\n"         -- single empty line
--   [""]
--   
-- --
--   >>> lines "one"        -- single unterminated line
--   ["one"]
--   
-- --
--   >>> lines "one\n"      -- single non-empty line
--   ["one"]
--   
-- --
--   >>> lines "one\n\n"    -- second line is empty
--   ["one",""]
--   
-- --
--   >>> lines "one\ntwo"   -- second line is unterminated
--   ["one","two"]
--   
-- --
--   >>> lines "one\ntwo\n" -- two non-empty lines
--   ["one","two"]
--   
lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space (as defined by isSpace). This function -- trims any white spaces at the beginning and at the end. -- --

Examples

-- --
--   >>> words "Lorem ipsum\ndolor"
--   ["Lorem","ipsum","dolor"]
--   
-- --
--   >>> words " foo bar "
--   ["foo","bar"]
--   
words :: String -> [String] -- | Appends a \n character to each input string, then -- concatenates the results. Equivalent to foldMap (s -> -- s ++ "\n"). -- --

Examples

-- --
--   >>> unlines ["Hello", "World", "!"]
--   "Hello\nWorld\n!\n"
--   
-- -- Note that unlines . lines /= -- id when the input is not \n-terminated: -- --
--   >>> unlines . lines $ "foo\nbar"
--   "foo\nbar\n"
--   
unlines :: [String] -> String -- | unwords joins words with separating spaces (U+0020 SPACE). -- -- unwords is neither left nor right inverse of words: -- --
--   >>> words (unwords [" "])
--   []
--   
--   >>> unwords (words "foo\nbar")
--   "foo bar"
--   
-- --

Examples

-- --
--   >>> unwords ["Lorem", "ipsum", "dolor"]
--   "Lorem ipsum dolor"
--   
-- --
--   >>> unwords ["foo", "bar", "", "baz"]
--   "foo bar  baz"
--   
unwords :: [String] -> String -- | <math>. 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. -- -- If there exists instance Ord a, it's faster to use -- nubOrd from the containers package (link to the -- latest online documentation), which takes only <math> time -- where d is the number of distinct elements in the list. -- -- Another approach to speed up nub is to use map -- Data.List.NonEmpty.head . -- Data.List.NonEmpty.group . sort, which takes -- <math> time, requires instance Ord a and doesn't -- preserve the order. -- --

Examples

-- --
--   >>> nub [1,2,3,4,3,2,1,2,4,3,5]
--   [1,2,3,4,5]
--   
-- --
--   >>> nub "hello, world!"
--   "helo, wrd!"
--   
nub :: Eq a => [a] -> [a] -- | <math>. delete x removes the first occurrence of -- x from its list argument. -- -- It is a special case of deleteBy, which allows the programmer -- to supply their own equality test. -- --

Examples

-- --
--   >>> delete 'a' "banana"
--   "bnana"
--   
-- --
--   >>> delete "not" ["haskell", "is", "not", "awesome"]
--   ["haskell","is","awesome"]
--   
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. -- --

Examples

-- --
--   >>> "Hello World!" \\ "ell W"
--   "Hoorld!"
--   
-- -- The second list must be finite, but the first may be infinite. -- --
--   >>> take 5 ([0..] \\ [2..4])
--   [0,1,5,6,7]
--   
-- --
--   >>> take 5 ([0..] \\ [2..])
--   * Hangs forever *
--   
(\\) :: Eq a => [a] -> [a] -> [a] infix 5 \\ -- | The union function returns the list union of the two lists. It -- is a special case of unionBy, which allows the programmer to -- supply their own equality test. -- --

Examples

-- --
--   >>> "dog" `union` "cow"
--   "dogcw"
--   
-- -- If equal elements are present in both lists, an element from the first -- list will be used. If the second list contains equal elements, only -- the first one will be retained: -- --
--   >>> import Data.Semigroup(Arg(..))
--   
--   >>> union [Arg () "dog"] [Arg () "cow"]
--   [Arg () "dog"]
--   
--   >>> union [] [Arg () "dog", Arg () "cow"]
--   [Arg () "dog"]
--   
-- -- However if the first list contains duplicates, so will the result: -- --
--   >>> "coot" `union` "duck"
--   "cootduk"
--   
--   >>> "duck" `union` "coot"
--   "duckot"
--   
-- -- union is productive even if both arguments are infinite. -- --
--   >>> [0, 2 ..] `union` [1, 3 ..]
--   [0,2,4,6,8,10,12..
--   
union :: Eq a => [a] -> [a] -> [a] -- | The intersect function takes the list intersection of two -- lists. It is a special case of intersectBy, which allows the -- programmer to supply their own equality test. -- --
Examples
-- --
--   >>> [1,2,3,4] `intersect` [2,4,6,8]
--   [2,4]
--   
-- -- If equal elements are present in both lists, an element from the first -- list will be used, and all duplicates from the second list quashed: -- --
--   >>> import Data.Semigroup
--   
--   >>> intersect [Arg () "dog"] [Arg () "cow", Arg () "cat"]
--   [Arg () "dog"]
--   
-- -- However if the first list contains duplicates, so will the result. -- --
--   >>> "coot" `intersect` "heron"
--   "oo"
--   
--   >>> "heron" `intersect` "coot"
--   "o"
--   
-- -- If the second list is infinite, intersect either hangs or -- returns its first argument in full. Otherwise if the first list is -- infinite, intersect might be productive: -- --
--   >>> intersect [100..] [0..]
--   [100,101,102,103...
--   
--   >>> intersect [0] [1..]
--   * Hangs forever *
--   
--   >>> intersect [1..] [0]
--   * Hangs forever *
--   
--   >>> intersect (cycle [1..3]) [2]
--   [2,2,2,2...
--   
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 lowest to highest, keeping duplicates in -- the order they appeared in the input. -- -- The argument must be finite. -- --

Examples

-- --
--   >>> sort [1,6,4,3,2,5]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> sort "haskell"
--   "aehklls"
--   
-- --
--   >>> import Data.Semigroup(Arg(..))
--   
--   >>> sort [Arg ":)" 0, Arg ":D" 0, Arg ":)" 1, Arg ":3" 0, Arg ":D" 1]
--   [Arg ":)" 0,Arg ":)" 1,Arg ":3" 0,Arg ":D" 0,Arg ":D" 1]
--   
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 lowest to highest, keeping duplicates in -- the order they appeared in the input. -- -- The argument must be finite. -- --

Examples

-- --
--   >>> sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
--   [(1,"Hello"),(2,"world"),(4,"!")]
--   
-- --
--   >>> sortOn length ["jim", "creed", "pam", "michael", "dwight", "kevin"]
--   ["jim","pam","creed","kevin","dwight","michael"]
--   
sortOn :: Ord b => (a -> b) -> [a] -> [a] -- | <math>. 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. -- --

Examples

-- --
--   >>> insert (-1) [1, 2, 3]
--   [-1,1,2,3]
--   
-- --
--   >>> insert 'd' "abcefg"
--   "abcdefg"
--   
-- --
--   >>> insert 4 [1, 2, 3, 5, 6, 7]
--   [1,2,3,4,5,6,7]
--   
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. -- --

Examples

-- --
--   >>> nubBy (\x y -> mod x 3 == mod y 3) [1,2,4,5,6]
--   [1,2,6]
--   
-- --
--   >>> nubBy (/=) [2, 7, 1, 8, 2, 8, 1, 8, 2, 8]
--   [2,2,2]
--   
-- --
--   >>> nubBy (>) [1, 2, 3, 2, 1, 5, 4, 5, 3, 2]
--   [1,2,3,5,5]
--   
nubBy :: (a -> a -> Bool) -> [a] -> [a] -- | <math>. The deleteBy function behaves like delete, -- but takes a user-supplied equality predicate. -- --

Examples

-- --
--   >>> deleteBy (<=) 4 [1..10]
--   [1,2,3,5,6,7,8,9,10]
--   
-- --
--   >>> deleteBy (/=) 5 [5, 5, 4, 3, 5, 2]
--   [5,5,3,5,2]
--   
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. This is the non-overloaded version of -- (\\). -- --
--   (\\) == deleteFirstsBy (==)
--   
-- -- The second list must be finite, but the first may be infinite. -- --

Examples

-- --
--   >>> deleteFirstsBy (>) [1..10] [3, 4, 5]
--   [4,5,6,7,8,9,10]
--   
-- --
--   >>> deleteFirstsBy (/=) [1..10] [1, 3, 5]
--   [4,5,6,7,8,9,10]
--   
deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The unionBy function is the non-overloaded version of -- union. Both arguments may be infinite. -- --

Examples

-- --
--   >>> unionBy (>) [3, 4, 5] [1, 2, 3, 4, 5, 6]
--   [3,4,5,4,5,6]
--   
-- --
--   >>> import Data.Semigroup (Arg(..))
--   
--   >>> unionBy (/=) [Arg () "Saul"] [Arg () "Kim"]
--   [Arg () "Saul", Arg () "Kim"]
--   
unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The intersectBy function is the non-overloaded version of -- intersect. It is productive for infinite arguments only if the -- first one is a subset of the second. intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The groupBy function is the non-overloaded version of -- group. -- -- When a supplied relation is not transitive, it is important to -- remember that equality is checked against the first element in the -- group, not against the nearest neighbour: -- --
--   >>> groupBy (\a b -> b - a < 5) [0..19]
--   [[0,1,2,3,4],[5,6,7,8,9],[10,11,12,13,14],[15,16,17,18,19]]
--   
-- -- It's often preferable to use -- Data.List.NonEmpty.groupBy, which provides type-level -- guarantees of non-emptiness of inner lists. -- --

Examples

-- --
--   >>> groupBy (/=) [1, 1, 1, 2, 3, 1, 4, 4, 5]
--   [[1],[1],[1,2,3],[1,4,4,5]]
--   
-- --
--   >>> groupBy (>) [1, 3, 5, 1, 4, 2, 6, 5, 4]
--   [[1],[3],[5,1,4,2],[6,5,4]]
--   
-- --
--   >>> groupBy (const not) [True, False, True, False, False, False, True]
--   [[True,False],[True,False,False,False],[True]]
--   
groupBy :: (a -> a -> Bool) -> [a] -> [[a]] -- | The sortBy function is the non-overloaded version of -- sort. The argument must be finite. -- -- The supplied comparison relation is supposed to be reflexive and -- antisymmetric, otherwise, e. g., for _ _ -> GT, the -- ordered list simply does not exist. The relation is also expected to -- be transitive: if it is not then sortBy might fail to find an -- ordered permutation, even if it exists. -- --

Examples

-- --
--   >>> sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")]
--   [(1,"Hello"),(2,"world"),(4,"!")]
--   
sortBy :: (a -> a -> Ordering) -> [a] -> [a] -- | <math>. The non-overloaded version of insert. -- --

Examples

-- --
--   >>> insertBy (\x y -> compare (length x) (length y)) [1, 2] [[1], [1, 2, 3], [1, 2, 3, 4]]
--   [[1],[1,2],[1,2,3],[1,2,3,4]]
--   
insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] -- | The largest element of a non-empty structure with respect to the given -- comparison function. -- --

Examples

-- -- Basic usage: -- --
--   >>> maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
--   "Longest"
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | The least element of a non-empty structure with respect to the given -- comparison function. -- --

Examples

-- -- Basic usage: -- --
--   >>> minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
--   "!"
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | <math>. 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. -- --

Examples

-- --
--   >>> genericLength [1, 2, 3] :: Int
--   3
--   
--   >>> genericLength [1, 2, 3] :: Float
--   3.0
--   
-- -- Users should take care to pick a return type that is wide enough to -- contain the full length of the list. If the width is insufficient, the -- overflow behaviour will depend on the (+) implementation in -- the selected Num instance. The following example overflows -- because the actual list length of 200 lies outside of the -- Int8 range of -128..127. -- --
--   >>> genericLength [1..200] :: Int8
--   -56
--   
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 and outputs the -- message to stderr. Depending on your terminal (settings), they may or -- may not be mixed. -- --
--   >>> let x = 123; f = show
--   
--   >>> trace ("calling f with x = " ++ show x) (f x)
--   calling f with x = 123
--   "123"
--   
-- -- 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 "hello"
--   hello
--   "hello"
--   
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 y: -- --
--   >>> let f x y = traceShow (x,y) (x + y) in f (1+2) 5
--   (3,5)
--   8
--   
traceShow :: Show a => a -> b -> b -- | Like traceShow but returns the shown value instead of a third -- value. -- --
--   >>> traceShowId (1+2+3, "hello" ++ "world")
--   (6,"helloworld")
--   (6,"helloworld")
--   
traceShowId :: Show a => a -> a -- | Like trace, but outputs the result of calling a function on the -- argument. -- --
--   >>> traceWith fst ("hello","world")
--   hello
--   ("hello","world")
--   
traceWith :: (a -> String) -> a -> a -- | Like traceWith, but uses show on the result of the -- function to convert it to a String. -- --
--   >>> traceShowWith length [1,2,3]
--   3
--   [1,2,3]
--   
traceShowWith :: Show b => (a -> b) -> 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 <- Just 3
--       traceM ("x: " ++ show x)
--       y <- pure 12
--       traceM ("y: " ++ show y)
--       pure (x*2 + y)
--   :}
--   x: 3
--   y: 12
--   Just 18
--   
traceM :: Applicative f => String -> f () -- | Like traceM, but uses show on the argument to convert it -- to a String. -- --
--   >>> :{
--   do
--       x <- Just 3
--       traceShowM x
--       y <- pure 12
--       traceShowM y
--       pure (x*2 + y)
--   :}
--   3
--   12
--   Just 18
--   
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 -- | Like traceEvent, but emits the result of calling a function on -- its argument. traceEventWith :: (a -> 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 () -- | Immediately flush the event log, if enabled. flushEventLog :: 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 -- | String is an alias for a list of characters. -- -- String constants in Haskell are values of type String. That -- means if you write a string literal like "hello world", it -- will have the type [Char], which is the same as -- String. -- -- Note: You can ask the compiler to automatically infer different -- types with the -XOverloadedStrings language extension, for -- example "hello world" :: Text. See IsString for more -- information. -- -- Because String is just a list of characters, you can use -- normal list functions to do basic string manipulation. See -- Data.List for operations on lists. -- --

Performance considerations

-- -- [Char] is a relatively memory-inefficient type. It is a -- linked list of boxed word-size characters, internally it looks -- something like: -- --
--   ╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭────╮
--   │ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ [] │
--   ╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰────╯
--           v               v               v
--          'a'             'b'             'c'
--   
-- -- The String "abc" will use 5*3+1 = 16 (in general -- 5n+1) words of space in memory. -- -- Furthermore, operations like (++) (string concatenation) are -- O(n) (in the left argument). -- -- For historical reasons, the base library uses String -- in a lot of places for the conceptual simplicity, but library code -- dealing with user-data should use the text package for Unicode -- text, or the the bytestring package for binary data. type String = [Char] -- | IsString is used in combination with the -- -XOverloadedStrings language extension to convert the -- literals to different string types. -- -- For example, if you use the text package, you can say -- --
--   {-# LANGUAGE OverloadedStrings  #-}
--   
--   myText = "hello world" :: Text
--   
-- -- Internally, the extension will convert this to the equivalent of -- --
--   myText = fromString @Text ("hello world" :: String)
--   
-- -- Note: You can use fromString in normal code as well, -- but the usual performance/memory efficiency problems with -- String apply. class IsString a fromString :: IsString a => String -> a -- | Splits the argument into a list of lines stripped of their -- terminating \n characters. The \n terminator is -- optional in a final non-empty line of the argument string. -- -- When the argument string is empty, or ends in a \n character, -- it can be recovered by passing the result of lines to the -- unlines function. Otherwise, unlines appends the missing -- terminating \n. This makes unlines . lines -- idempotent: -- --
--   (unlines . lines) . (unlines . lines) = (unlines . lines)
--   
-- --

Examples

-- --
--   >>> lines ""           -- empty input contains no lines
--   []
--   
-- --
--   >>> lines "\n"         -- single empty line
--   [""]
--   
-- --
--   >>> lines "one"        -- single unterminated line
--   ["one"]
--   
-- --
--   >>> lines "one\n"      -- single non-empty line
--   ["one"]
--   
-- --
--   >>> lines "one\n\n"    -- second line is empty
--   ["one",""]
--   
-- --
--   >>> lines "one\ntwo"   -- second line is unterminated
--   ["one","two"]
--   
-- --
--   >>> lines "one\ntwo\n" -- two non-empty lines
--   ["one","two"]
--   
lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space (as defined by isSpace). This function -- trims any white spaces at the beginning and at the end. -- --

Examples

-- --
--   >>> words "Lorem ipsum\ndolor"
--   ["Lorem","ipsum","dolor"]
--   
-- --
--   >>> words " foo bar "
--   ["foo","bar"]
--   
words :: String -> [String] -- | Appends a \n character to each input string, then -- concatenates the results. Equivalent to foldMap (s -> -- s ++ "\n"). -- --

Examples

-- --
--   >>> unlines ["Hello", "World", "!"]
--   "Hello\nWorld\n!\n"
--   
-- -- Note that unlines . lines /= -- id when the input is not \n-terminated: -- --
--   >>> unlines . lines $ "foo\nbar"
--   "foo\nbar\n"
--   
unlines :: [String] -> String -- | unwords joins words with separating spaces (U+0020 SPACE). -- -- unwords is neither left nor right inverse of words: -- --
--   >>> words (unwords [" "])
--   []
--   
--   >>> unwords (words "foo\nbar")
--   "foo bar"
--   
-- --

Examples

-- --
--   >>> unwords ["Lorem", "ipsum", "dolor"]
--   "Lorem ipsum dolor"
--   
-- --
--   >>> unwords ["foo", "bar", "", "baz"]
--   "foo bar  baz"
--   
unwords :: [String] -> String instance forall a k (b :: k). 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.~ 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.Classes.Eq Data.Version.Version instance GHC.Generics.Generic Data.Version.Version instance GHC.Classes.Ord Data.Version.Version instance GHC.Read.Read Data.Version.Version instance GHC.Show.Show Data.Version.Version module GHC.IsList -- | The IsList class and its methods are intended to be used in -- conjunction with the OverloadedLists extension. class IsList l where { -- | The Item type function returns the type of items of the -- structure l. type 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 and -- potentially uses it to construct the structure l more -- efficiently compared to fromList. If the given number does not -- equal to the input list's length the behaviour of fromListN is -- not specified. -- --
--   fromListN (length xs) xs == fromList xs
--   
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.IsList.IsList GHC.Stack.Types.CallStack instance GHC.IsList.IsList [a] instance GHC.IsList.IsList (GHC.Base.NonEmpty a) instance GHC.IsList.IsList Data.Version.Version instance GHC.IsList.IsList (Control.Applicative.ZipList a) -- | The Functor, Monad and MonadPlus classes, with -- some useful operations on monads. module Control.Monad -- | A type f is a Functor if it provides a function fmap -- which, given any types a and b lets you apply any -- function from (a -> b) to turn an f a into an -- f b, preserving the structure of f. Furthermore -- f needs to adhere to the following: -- -- -- -- Note, that the second law follows from the free theorem of the type -- fmap and the first law, so you need only check that the former -- condition holds. See -- https://www.schoolofhaskell.com/user/edwardk/snippets/fmap or -- https://github.com/quchen/articles/blob/master/second_functor_law.md -- for an explanation. class Functor (f :: Type -> Type) -- | fmap is used to apply a function of type (a -> b) -- to a value of type f a, where f is a functor, to produce a -- value of type f b. Note that for any type constructor with -- more than one parameter (e.g., Either), only the last type -- parameter can be modified with fmap (e.g., b in -- `Either a b`). -- -- Some type constructors with two parameters or more have a -- Bifunctor instance that allows both the last and the -- penultimate parameters to be mapped over. -- --

Examples

-- -- Convert from a Maybe Int to a Maybe String -- using show: -- --
--   >>> fmap show Nothing
--   Nothing
--   
--   >>> fmap show (Just 3)
--   Just "3"
--   
-- -- Convert from an Either Int Int to an Either Int -- String using show: -- --
--   >>> fmap show (Left 17)
--   Left 17
--   
--   >>> fmap show (Right 17)
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> fmap (*2) [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> fmap even (2,2)
--   (2,True)
--   
-- -- It may seem surprising that the function is only applied to the last -- element of the tuple compared to the list example above which applies -- it to every element in the list. To understand, remember that tuples -- are type constructors with multiple type parameters: a tuple of 3 -- elements (a,b,c) can also be written (,,) a b c and -- its Functor instance is defined for Functor ((,,) a -- b) (i.e., only the third parameter is free to be mapped over with -- fmap). -- -- It explains why fmap can be used with tuples containing -- values of different types as in the following example: -- --
--   >>> fmap even ("hello", 1.0, 4)
--   ("hello",1.0,True)
--   
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. -- --

Examples

-- -- Perform a computation with Maybe and replace the result with a -- constant value if it is Just: -- --
--   >>> 'a' <$ Just 2
--   Just 'a'
--   
--   >>> 'a' <$ Nothing
--   Nothing
--   
(<$) :: Functor f => a -> f b -> f a infixl 4 <$ -- | 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: -- -- -- -- 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 :: Type -> Type) -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. -- -- 'as >>= bs' can be understood as the do -- expression -- --
--   do a <- as
--      bs a
--   
(>>=) :: 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. -- -- 'as >> bs' can be understood as the do -- expression -- --
--   do as
--      bs
--   
(>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a infixl 1 >>= infixl 1 >> -- | 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
--   
-- -- fail s should be an action that runs in the monad itself, not -- an exception (except in instances of MonadIO). In particular, -- fail should not be implemented in terms of error. class Monad m => MonadFail (m :: Type -> Type) fail :: MonadFail m => String -> m a -- | Monads that also support choice and failure. class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) -- | The identity of mplus. It should also satisfy the equations -- --
--   mzero >>= f  =  mzero
--   v >> mzero   =  mzero
--   
-- -- The default definition is -- --
--   mzero = empty
--   
mzero :: MonadPlus m => m a -- | An associative operation. The default definition is -- --
--   mplus = (<|>)
--   
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_. -- --

Examples

-- -- mapM is literally a traverse with a type signature -- restricted to Monad. Its implementation may be more efficient -- due to additional power of Monad. 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. -- -- mapM_ is just like traverse_, but specialised to monadic -- actions. 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. -- -- forM_ is just like for_, but specialised to monadic -- actions. 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_. -- --

Examples

-- -- Basic usage: -- -- The first two examples are instances where the input and and output of -- sequence are isomorphic. -- --
--   >>> sequence $ Right [1,2,3,4]
--   [Right 1,Right 2,Right 3,Right 4]
--   
-- --
--   >>> sequence $ [Right 1,Right 2,Right 3,Right 4]
--   Right [1,2,3,4]
--   
-- -- The following examples demonstrate short circuit behavior for -- sequence. -- --
--   >>> sequence $ Left [1,2,3,4]
--   Left [1,2,3,4]
--   
-- --
--   >>> sequence $ [Left 0, Right 1,Right 2,Right 3,Right 4]
--   Left 0
--   
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. -- -- sequence_ is just like sequenceA_, but specialised to -- monadic actions. 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 composition of Kleisli arrows. -- -- '(bs >=> cs) a' can be understood as the -- do expression -- --
--   do b <- bs a
--      cs b
--   
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 >=> -- | Right-to-left composition of Kleisli arrows. -- (>=>), 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 <=< -- | Repeat an action indefinitely. -- --

Examples

-- -- A common use of forever is to process input from network -- sockets, Handles, and channels (e.g. MVar and -- Chan). -- -- For example, here is how we might implement an echo server, -- using forever both to listen for client connections on a -- network socket and to echo client input on client connection handles: -- --
--   echoServer :: Socket -> IO ()
--   echoServer socket = forever $ do
--     client <- accept socket
--     forkFinally (echo client) (\_ -> hClose client)
--     where
--       echo :: Handle -> IO ()
--       echo client = forever $
--         hGetLine client >>= hPutStrLn client
--   
-- -- Note that "forever" isn't necessarily non-terminating. If the action -- is in a MonadPlus and short-circuits after some number -- of iterations. then forever actually returns -- mzero, effectively short-circuiting its caller. 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 bss' can be understood as the do -- expression -- --
--   do bs <- bss
--      bs
--   
-- --

Examples

-- -- A common use of join is to run an IO computation -- returned from an STM transaction, since STM transactions -- can't perform IO directly. Recall that -- --
--   atomically :: STM a -> IO a
--   
-- -- is used to run STM transactions atomically. So, by specializing -- the types of atomically and join to -- --
--   atomically :: STM (IO b) -> IO (IO b)
--   join       :: IO (IO b)  -> IO b
--   
-- -- we can compose them as -- --
--   join . atomically :: STM (IO b) -> IO b
--   
-- -- to run an STM transaction and the IO action it returns. join :: Monad m => m (m a) -> m a -- | The sum of a collection of actions using (<|>), -- generalizing concat. -- -- msum is just like asum, but specialised to -- MonadPlus. -- --

Examples

-- -- Basic usage, using the MonadPlus instance for Maybe: -- --
--   >>> msum [Just "Hello", Nothing, Just "World"]
--   Just "Hello"
--   
msum :: (Foldable t, MonadPlus m) => t (m a) -> m a -- | Direct MonadPlus equivalent of filter. -- --

Examples

-- -- The filter function is just mfilter specialized to the -- list monad: -- --
--   filter = ( mfilter :: (a -> Bool) -> [a] -> [a] )
--   
-- -- An example using mfilter with the Maybe monad: -- --
--   >>> 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 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 act -- n times, and then returns the list of results: -- --

Examples

-- --
--   >>> import Control.Monad.State
--   
--   >>> runState (replicateM 3 $ state $ \s -> (s, s + 1)) 1
--   ([1,2,3],4)
--   
replicateM :: Applicative m => Int -> m a -> m [a] -- | Like replicateM, but discards the result. -- --

Examples

-- --
--   >>> replicateM_ 3 (putStrLn "a")
--   a
--   a
--   a
--   
replicateM_ :: Applicative m => Int -> m a -> m () -- | Conditional failure of Alternative computations. Defined by -- --
--   guard True  = pure ()
--   guard False = empty
--   
-- --

Examples

-- -- Common uses of guard include conditionally signalling an error -- in an error monad and conditionally rejecting the current choice in an -- Alternative-based parser. -- -- As an example of signalling an error in the error monad Maybe, -- consider a safe division function safeDiv x y that returns -- Nothing when the denominator y is zero and -- Just (x `div` y) otherwise. For example: -- --
--   >>> safeDiv 4 0
--   Nothing
--   
-- --
--   >>> safeDiv 4 2
--   Just 2
--   
-- -- A definition of safeDiv using guards, but not guard: -- --
--   safeDiv :: Int -> Int -> Maybe Int
--   safeDiv x y | y /= 0    = Just (x `div` y)
--               | otherwise = Nothing
--   
-- -- A definition of safeDiv using guard and Monad -- do-notation: -- --
--   safeDiv :: Int -> Int -> Maybe Int
--   safeDiv x y = do
--     guard (y /= 0)
--     return (x `div` y)
--   
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", lazy in the second argument (&&) :: Bool -> Bool -> Bool infixr 3 && -- | Boolean "or", lazy in the second argument (||) :: 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 represents Unicode codespace and its -- elements are code points as in definitions D9 and D10 of the -- Unicode Standard. -- -- Character literals in Haskell are single-quoted: 'Q', -- 'Я' or 'Ω'. To represent a single quote itself use -- '\'', and to represent a backslash use '\\'. The -- full grammar can be found in the section 2.6 of the Haskell 2010 -- Language Report. -- -- To specify a character by its code point one can use decimal, -- hexadecimal or octal notation: '\65', '\x41' and -- '\o101' are all alternative forms of 'A'. The -- largest code point is '\x10ffff'. -- -- There is a special escape syntax for ASCII control characters: -- -- TODO: table -- -- Data.Char provides utilities to work with Char. data Char -- | String is an alias for a list of characters. -- -- String constants in Haskell are values of type String. That -- means if you write a string literal like "hello world", it -- will have the type [Char], which is the same as -- String. -- -- Note: You can ask the compiler to automatically infer different -- types with the -XOverloadedStrings language extension, for -- example "hello world" :: Text. See IsString for more -- information. -- -- Because String is just a list of characters, you can use -- normal list functions to do basic string manipulation. See -- Data.List for operations on lists. -- --

Performance considerations

-- -- [Char] is a relatively memory-inefficient type. It is a -- linked list of boxed word-size characters, internally it looks -- something like: -- --
--   ╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭────╮
--   │ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ [] │
--   ╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰────╯
--           v               v               v
--          'a'             'b'             'c'
--   
-- -- The String "abc" will use 5*3+1 = 16 (in general -- 5n+1) words of space in memory. -- -- Furthermore, operations like (++) (string concatenation) are -- O(n) (in the left argument). -- -- For historical reasons, the base library uses String -- in a lot of places for the conceptual simplicity, but library code -- dealing with user-data should use the text package for Unicode -- text, or the the bytestring package for binary data. 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. -- --

Examples

-- --
--   >>> curry fst 1 2
--   1
--   
curry :: ((a, b) -> c) -> a -> b -> c -- | uncurry converts a curried function to a function on pairs. -- --

Examples

-- --
--   >>> uncurry (+) (1,2)
--   3
--   
-- --
--   >>> uncurry ($) (show, 1)
--   "1"
--   
-- --
--   >>> map (uncurry max) [(1,2), (3,4), (6,8)]
--   [2,4,8]
--   
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. -- -- The Haskell Report defines no laws for Eq. However, instances -- are encouraged to follow these properties: -- -- -- -- Minimal complete definition: either == or /=. class Eq a (==) :: Eq a => a -> a -> Bool (/=) :: Eq a => a -> a -> Bool infix 4 == infix 4 /= -- | 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. -- -- Ord, as defined by the Haskell report, implements a total order -- and has the following properties: -- -- -- -- The following operator interactions are expected to hold: -- --
    --
  1. x >= y = y <= x
  2. --
  3. x < y = x <= y && x /= y
  4. --
  5. x > y = y < x
  6. --
  7. x < y = compare x y == LT
  8. --
  9. x > y = compare x y == GT
  10. --
  11. x == y = compare x y == EQ
  12. --
  13. min x y == if x <= y then x else y = True
  14. --
  15. max x y == if x >= y then x else y = True
  16. --
-- -- Note that (7.) and (8.) do not require min and -- max to return either of their arguments. The result is merely -- required to equal one of the arguments in terms of (==). -- -- 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 infix 4 >= infix 4 < infix 4 <= infix 4 > -- | 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..] with [n..] = -- enumFrom n, a possible implementation being enumFrom n = n : -- enumFrom (succ n). For example: -- -- enumFrom :: Enum a => a -> [a] -- | Used in Haskell's translation of [n,n'..] with [n,n'..] = -- enumFromThen n n', a possible implementation being -- enumFromThen n n' = n : n' : worker (f x) (f x n'), -- worker s v = v : worker s (s v), x = fromEnum n' - -- fromEnum n and f n y | n > 0 = f (n - 1) (succ y) | n < -- 0 = f (n + 1) (pred y) | otherwise = y For example: -- -- enumFromThen :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n..m] with [n..m] = -- enumFromTo n m, a possible implementation being enumFromTo n -- m | n <= m = n : enumFromTo (succ n) m | otherwise = []. For -- example: -- -- enumFromTo :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n,n'..m] with [n,n'..m] -- = enumFromThenTo n n' m, a possible implementation being -- enumFromThenTo n n' m = worker (f x) (c x) n m, x = -- fromEnum n' - fromEnum n, c x = bool (>=) ((x -- 0) f n y | n > 0 = f (n - 1) (succ y) | n < 0 = f (n + -- 1) (pred y) | otherwise = y and worker s c v m | c v m = v : -- worker s c (s v) m | otherwise = [] For example: -- -- 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 :: Bounded a => a maxBound :: Bounded a => a -- | A fixed-precision integer type with at least the range [-2^29 .. -- 2^29-1]. The exact range for a given implementation can be -- determined by using minBound and maxBound from the -- Bounded class. data Int -- | Arbitrary precision integers. In contrast with fixed-size integral -- types such as Int, the Integer type represents the -- entire infinite range of integers. -- -- Integers are stored in a kind of sign-magnitude form, hence do not -- expect two's complement form when using bit operations. -- -- If the value is small (fit into an Int), IS constructor -- is used. Otherwise IP and IN constructors are used to -- store a BigNat representing respectively the positive or the -- negative value magnitude. -- -- Invariant: IP and IN are used iff value doesn't fit in -- IS 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. -- -- The Haskell Report defines no laws for Num. However, -- (+) and (*) are customarily expected -- to define a ring and have the following properties: -- -- -- -- Note that it isn't customarily expected that a type instance of -- both Num and Ord implement an ordered ring. Indeed, in -- base only Integer and Rational do. 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 infixl 6 - infixl 6 + infixl 7 * -- | Real numbers. -- -- The Haskell report defines no laws for Real, however -- Real instances are customarily expected to adhere to the -- following law: -- -- -- -- The law does not hold for Float, Double, CFloat, -- CDouble, etc., because these types contain non-finite values, -- which cannot be roundtripped through Rational. 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. -- -- The Haskell Report defines no laws for Integral. However, -- Integral instances are customarily expected to define a -- Euclidean domain and have the following properties for the -- div/mod and quot/rem pairs, given suitable -- Euclidean functions f and g: -- -- -- -- An example of a suitable Euclidean function, for Integer's -- instance, is abs. -- -- In addition, toInteger should be total, and -- fromInteger should be a left inverse for it, i.e. -- fromInteger (toInteger i) = i. class (Real a, Enum a) => Integral a -- | integer division truncated toward zero -- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. quot :: Integral a => a -> a -> a -- | integer remainder, satisfying -- --
--   (x `quot` y)*y + (x `rem` y) == x
--   
-- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. rem :: Integral a => a -> a -> a -- | integer division truncated toward negative infinity -- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. div :: Integral a => a -> a -> a -- | integer modulus, satisfying -- --
--   (x `div` y)*y + (x `mod` y) == x
--   
-- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. mod :: Integral a => a -> a -> a -- | simultaneous quot and rem -- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. quotRem :: Integral a => a -> a -> (a, a) -- | simultaneous div and mod -- -- WARNING: This function is partial (because it throws when 0 is passed -- as the divisor) for all the integer types in base. divMod :: Integral a => a -> a -> (a, a) -- | conversion to Integer toInteger :: Integral a => a -> Integer infixl 7 `quot` infixl 7 `rem` infixl 7 `div` infixl 7 `mod` -- | Fractional numbers, supporting real division. -- -- The Haskell Report defines no laws for Fractional. However, -- (+) and (*) are customarily expected -- to define a division ring and have the following properties: -- -- -- -- Note that it isn't customarily expected that a type instance of -- Fractional implement a field. However, all instances in -- base do. 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 infixl 7 / -- | Trigonometric and hyperbolic functions and related functions. -- -- The Haskell Report defines no laws for Floating. However, -- (+), (*) and exp are -- customarily expected to define an exponential field and have the -- following properties: -- -- class Fractional a => Floating a pi :: Floating a => a exp :: Floating a => a -> a log :: Floating a => a -> a sqrt :: Floating a => a -> a (**) :: Floating a => a -> a -> a logBase :: Floating a => a -> a -> a sin :: Floating a => a -> a cos :: Floating a => a -> a tan :: Floating a => a -> a asin :: Floating a => a -> a acos :: Floating a => a -> a atan :: Floating a => a -> a sinh :: Floating a => a -> a cosh :: Floating a => a -> a tanh :: Floating a => a -> a asinh :: Floating a => a -> a acosh :: Floating a => a -> a atanh :: Floating a => a -> a infixr 8 ** -- | 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. -- -- WARNING: This function performs silent truncation if the result type -- is not at least as big as the argument's type. fromIntegral :: (Integral a, Num b) => a -> b -- | General coercion to Fractional types. -- -- WARNING: This function goes through the Rational type, which -- does not have values for NaN for example. This means it does -- not round-trip. -- -- For Double it also behaves differently with or without -O0: -- --
--   Prelude> realToFrac nan -- With -O0
--   -Infinity
--   Prelude> realToFrac nan
--   NaN
--   
realToFrac :: (Real a, Fractional b) => a -> b -- | The class of semigroups (types with an associative binary operation). -- -- Instances should satisfy the following: -- -- -- -- You can alternatively define sconcat instead of -- (<>), in which case the laws are: -- -- class Semigroup a -- | An associative operation. -- --

Examples

-- --
--   >>> [1,2,3] <> [4,5,6]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> Just [1, 2, 3] <> Just [4, 5, 6]
--   Just [1,2,3,4,5,6]
--   
-- --
--   >>> putStr "Hello, " <> putStrLn "World!"
--   Hello, World!
--   
(<>) :: Semigroup a => a -> a -> a infixr 6 <> -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following: -- -- -- -- You can alternatively define mconcat instead of mempty, -- in which case the laws are: -- -- -- -- 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. -- -- NOTE: Semigroup is a superclass of Monoid since -- base-4.11.0.0. class Semigroup a => Monoid a -- | Identity of mappend -- --

Examples

-- --
--   >>> "Hello world" <> mempty
--   "Hello world"
--   
-- --
--   >>> mempty <> [1, 2, 3]
--   [1,2,3]
--   
mempty :: Monoid a => a -- | An associative operation -- -- NOTE: This method is redundant and has the default -- implementation mappend = (<>) since -- base-4.11.0.0. Should it be implemented manually, since -- mappend is a synonym for (<>), it is expected that -- the two functions are defined the same way. In a future GHC release -- mappend will be removed from Monoid. 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 ["Hello", " ", "Haskell", "!"]
--   "Hello Haskell!"
--   
mconcat :: Monoid a => [a] -> a -- | A type f is a Functor if it provides a function fmap -- which, given any types a and b lets you apply any -- function from (a -> b) to turn an f a into an -- f b, preserving the structure of f. Furthermore -- f needs to adhere to the following: -- -- -- -- Note, that the second law follows from the free theorem of the type -- fmap and the first law, so you need only check that the former -- condition holds. See -- https://www.schoolofhaskell.com/user/edwardk/snippets/fmap or -- https://github.com/quchen/articles/blob/master/second_functor_law.md -- for an explanation. class Functor (f :: Type -> Type) -- | fmap is used to apply a function of type (a -> b) -- to a value of type f a, where f is a functor, to produce a -- value of type f b. Note that for any type constructor with -- more than one parameter (e.g., Either), only the last type -- parameter can be modified with fmap (e.g., b in -- `Either a b`). -- -- Some type constructors with two parameters or more have a -- Bifunctor instance that allows both the last and the -- penultimate parameters to be mapped over. -- --

Examples

-- -- Convert from a Maybe Int to a Maybe String -- using show: -- --
--   >>> fmap show Nothing
--   Nothing
--   
--   >>> fmap show (Just 3)
--   Just "3"
--   
-- -- Convert from an Either Int Int to an Either Int -- String using show: -- --
--   >>> fmap show (Left 17)
--   Left 17
--   
--   >>> fmap show (Right 17)
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> fmap (*2) [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> fmap even (2,2)
--   (2,True)
--   
-- -- It may seem surprising that the function is only applied to the last -- element of the tuple compared to the list example above which applies -- it to every element in the list. To understand, remember that tuples -- are type constructors with multiple type parameters: a tuple of 3 -- elements (a,b,c) can also be written (,,) a b c and -- its Functor instance is defined for Functor ((,,) a -- b) (i.e., only the third parameter is free to be mapped over with -- fmap). -- -- It explains why fmap can be used with tuples containing -- values of different types as in the following example: -- --
--   >>> fmap even ("hello", 1.0, 4)
--   ("hello",1.0,True)
--   
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. -- --

Examples

-- -- Perform a computation with Maybe and replace the result with a -- constant value if it is Just: -- --
--   >>> 'a' <$ Just 2
--   Just 'a'
--   
--   >>> 'a' <$ Nothing
--   Nothing
--   
(<$) :: Functor f => a -> f b -> f a 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 <$> -- | 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 :: Type -> Type) -- | 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. -- --

Example

-- -- Used in combination with (<$>), -- (<*>) can be used to build a record. -- --
--   >>> data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
--   
-- --
--   >>> produceFoo :: Applicative f => f Foo
--   
-- --
--   >>> produceBar :: Applicative f => f Bar
--   
--   >>> produceBaz :: Applicative f => f Baz
--   
-- --
--   >>> mkState :: Applicative f => f MyState
--   
--   >>> mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz
--   
(<*>) :: 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 <*>. -- -- This became a typeclass method in 4.10.0.0. Prior to that, it was a -- function defined in terms of <*> and fmap. -- --

Example

-- --
--   >>> liftA2 (,) (Just 3) (Just 5)
--   Just (3,5)
--   
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c -- | Sequence actions, discarding the value of the first argument. -- --

Examples

-- -- If used in conjunction with the Applicative instance for Maybe, -- you can chain Maybe computations, with a possible "early return" in -- case of Nothing. -- --
--   >>> Just 2 *> Just 3
--   Just 3
--   
-- --
--   >>> Nothing *> Just 3
--   Nothing
--   
-- -- Of course a more interesting use case would be to have effectful -- computations instead of just returning pure values. -- --
--   >>> import Data.Char
--   
--   >>> import Text.ParserCombinators.ReadP
--   
--   >>> let p = string "my name is " *> munch1 isAlpha <* eof
--   
--   >>> readP_to_S p "my name is Simon"
--   [("Simon","")]
--   
(*>) :: 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 infixl 4 <*> infixl 4 *> infixl 4 <* -- | 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: -- -- -- -- 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 :: Type -> Type) -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. -- -- 'as >>= bs' can be understood as the do -- expression -- --
--   do a <- as
--      bs a
--   
(>>=) :: 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. -- -- 'as >> bs' can be understood as the do -- expression -- --
--   do as
--      bs
--   
(>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a infixl 1 >>= infixl 1 >> -- | 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
--   
-- -- fail s should be an action that runs in the monad itself, not -- an exception (except in instances of MonadIO). In particular, -- fail should not be implemented in terms of error. class Monad m => MonadFail (m :: Type -> Type) fail :: MonadFail 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. -- -- mapM_ is just like traverse_, but specialised to monadic -- actions. 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. -- -- sequence_ is just like sequenceA_, but specialised to -- monadic actions. 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 =<< -- | The Foldable class represents data structures that can be reduced to a -- summary value one element at a time. Strict left-associative folds are -- a good fit for space-efficient reduction, while lazy right-associative -- folds are a good fit for corecursive iteration, or for folds that -- short-circuit after processing an initial subsequence of the -- structure's elements. -- -- Instances can be derived automatically by enabling the -- DeriveFoldable extension. For example, a derived instance for -- a binary tree might be: -- --
--   {-# LANGUAGE DeriveFoldable #-}
--   data Tree a = Empty
--               | Leaf a
--               | Node (Tree a) a (Tree a)
--       deriving Foldable
--   
-- -- A more detailed description can be found in the Overview -- section of Data.Foldable#overview. -- -- For the class laws see the Laws section of -- Data.Foldable#laws. class Foldable (t :: Type -> Type) -- | Map each element of the structure into a monoid, and combine the -- results with (<>). This fold is -- right-associative and lazy in the accumulator. For strict -- left-associative folds consider foldMap' instead. -- --

Examples

-- -- Basic usage: -- --
--   >>> foldMap Sum [1, 3, 5]
--   Sum {getSum = 9}
--   
-- --
--   >>> foldMap Product [1, 3, 5]
--   Product {getProduct = 15}
--   
-- --
--   >>> foldMap (replicate 3) [1, 2, 3]
--   [1,1,1,2,2,2,3,3,3]
--   
-- -- When a Monoid's (<>) is lazy in its second -- argument, foldMap can return a result even from an unbounded -- structure. For example, lazy accumulation enables -- Data.ByteString.Builder to efficiently serialise large data -- structures and produce the output incrementally: -- --
--   >>> import qualified Data.ByteString.Lazy as L
--   
--   >>> import qualified Data.ByteString.Builder as B
--   
--   >>> let bld :: Int -> B.Builder; bld i = B.intDec i <> B.word8 0x20
--   
--   >>> let lbs = B.toLazyByteString $ foldMap bld [0..]
--   
--   >>> L.take 64 lbs
--   "0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24"
--   
foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | Right-associative fold of a structure, lazy in the accumulator. -- -- 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, given an -- operator lazy in its right argument, foldr can produce a -- terminating expression from an unbounded list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldr f z = foldr f z . toList
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> foldr (||) False [False, True, False]
--   True
--   
-- --
--   >>> foldr (||) False []
--   False
--   
-- --
--   >>> foldr (\c acc -> acc ++ [c]) "foo" ['a', 'b', 'c', 'd']
--   "foodcba"
--   
-- --
Infinite structures
-- -- ⚠️ Applying foldr to infinite structures usually doesn't -- terminate. -- -- It may still terminate under one of the following conditions: -- -- -- --
Short-circuiting
-- -- (||) short-circuits on True values, so the -- following terminates because there is a True value finitely far -- from the left side: -- --
--   >>> foldr (||) False (True : repeat False)
--   True
--   
-- -- But the following doesn't terminate: -- --
--   >>> foldr (||) False (repeat False ++ [True])
--   * Hangs forever *
--   
-- --
Laziness in the second argument
-- -- Applying foldr to infinite structures terminates when the -- operator is lazy in its second argument (the initial accumulator is -- never used in this case, and so could be left undefined, but -- [] is more clear): -- --
--   >>> take 5 $ foldr (\i acc -> i : fmap (+3) acc) [] (repeat 1)
--   [1,4,7,10,13]
--   
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Left-associative fold of a structure, lazy in the accumulator. This is -- rarely what you want, but can work well for structures with efficient -- right-to-left sequencing and an operator that is lazy in its left -- argument. -- -- 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. Like all left-associative folds, -- foldl will diverge if given an infinite list. -- -- If you want an efficient strict left-fold, you probably want to use -- foldl' instead of foldl. The reason for this is that the -- 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
--   
-- --

Examples

-- -- The first example is a strict fold, which in practice is best -- performed with foldl'. -- --
--   >>> foldl (+) 42 [1,2,3,4]
--   52
--   
-- -- Though the result below is lazy, the input is reversed before -- prepending it to the initial accumulator, so corecursion begins only -- after traversing the entire input string. -- --
--   >>> foldl (\acc c -> c : acc) "abcd" "efgh"
--   "hgfeabcd"
--   
-- -- A left fold of a structure that is infinite on the right cannot -- terminate, even when for any finite input the fold just returns the -- initial accumulator: -- --
--   >>> foldl (\a _ -> a) 0 $ repeat 1
--   * Hangs forever *
--   
-- -- WARNING: When it comes to lists, you always want to use either -- foldl' or foldr instead. 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. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. -- --

Examples

-- -- Basic usage: -- --
--   >>> foldr1 (+) [1..4]
--   10
--   
-- --
--   >>> foldr1 (+) []
--   Exception: Prelude.foldr1: empty list
--   
-- --
--   >>> foldr1 (+) Nothing
--   *** Exception: foldr1: empty structure
--   
-- --
--   >>> foldr1 (-) [1..4]
--   -2
--   
-- --
--   >>> foldr1 (&&) [True, False, True, True]
--   False
--   
-- --
--   >>> foldr1 (||) [False, False, True, True]
--   True
--   
-- --
--   >>> foldr1 (+) [1..]
--   * Hangs forever *
--   
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. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. -- --
--   foldl1 f = foldl1 f . toList
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> foldl1 (+) [1..4]
--   10
--   
-- --
--   >>> foldl1 (+) []
--   *** Exception: Prelude.foldl1: empty list
--   
-- --
--   >>> foldl1 (+) Nothing
--   *** Exception: foldl1: empty structure
--   
-- --
--   >>> foldl1 (-) [1..4]
--   -8
--   
-- --
--   >>> foldl1 (&&) [True, False, True, True]
--   False
--   
-- --
--   >>> foldl1 (||) [False, False, True, True]
--   True
--   
-- --
--   >>> foldl1 (+) [1..]
--   * Hangs forever *
--   
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a -- | Does the element occur in the structure? -- -- Note: elem is often used in infix form. -- --

Examples

-- -- Basic usage: -- --
--   >>> 3 `elem` []
--   False
--   
-- --
--   >>> 3 `elem` [1,2]
--   False
--   
-- --
--   >>> 3 `elem` [1,2,3,4,5]
--   True
--   
-- -- For infinite structures, the default implementation of elem -- terminates if the sought-after value exists at a finite distance from -- the left side of the structure: -- --
--   >>> 3 `elem` [1..]
--   True
--   
-- --
--   >>> 3 `elem` ([4..] ++ [3])
--   * Hangs forever *
--   
elem :: (Foldable t, Eq a) => a -> t a -> Bool -- | The largest element of a non-empty structure. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. A structure that supports random access -- and maintains its elements in order should provide a specialised -- implementation to return the maximum in faster than linear time. -- --

Examples

-- -- Basic usage: -- --
--   >>> maximum [1..10]
--   10
--   
-- --
--   >>> maximum []
--   *** Exception: Prelude.maximum: empty list
--   
-- --
--   >>> maximum Nothing
--   *** Exception: maximum: empty structure
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. maximum :: (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure. -- -- This function is non-total and will raise a runtime exception if the -- structure happens to be empty. A structure that supports random access -- and maintains its elements in order should provide a specialised -- implementation to return the minimum in faster than linear time. -- --

Examples

-- -- Basic usage: -- --
--   >>> minimum [1..10]
--   1
--   
-- --
--   >>> minimum []
--   *** Exception: Prelude.minimum: empty list
--   
-- --
--   >>> minimum Nothing
--   *** Exception: minimum: empty structure
--   
-- -- WARNING: This function is partial for possibly-empty structures like -- lists. minimum :: (Foldable t, Ord a) => t a -> a -- | The sum function computes the sum of the numbers of a -- structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> sum []
--   0
--   
-- --
--   >>> sum [42]
--   42
--   
-- --
--   >>> sum [1..10]
--   55
--   
-- --
--   >>> sum [4.1, 2.0, 1.7]
--   7.8
--   
-- --
--   >>> sum [1..]
--   * Hangs forever *
--   
sum :: (Foldable t, Num a) => t a -> a -- | The product function computes the product of the numbers of a -- structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> product []
--   1
--   
-- --
--   >>> product [42]
--   42
--   
-- --
--   >>> product [1..10]
--   3628800
--   
-- --
--   >>> product [4.1, 2.0, 1.7]
--   13.939999999999998
--   
-- --
--   >>> product [1..]
--   * Hangs forever *
--   
product :: (Foldable t, Num a) => t a -> a infix 4 `elem` -- | Functors representing data structures that can be transformed to -- structures of the same shape by performing an -- Applicative (or, therefore, Monad) action on each -- element from left to right. -- -- A more detailed description of what same shape means, the -- various methods, how traversals are constructed, and example advanced -- use-cases can be found in the Overview section of -- Data.Traversable#overview. -- -- For the class laws see the Laws section of -- Data.Traversable#laws. class (Functor t, Foldable t) => Traversable (t :: Type -> Type) -- | 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_. -- --

Examples

-- -- Basic usage: -- -- In the first two examples we show each evaluated action mapping to the -- output structure. -- --
--   >>> traverse Just [1,2,3,4]
--   Just [1,2,3,4]
--   
-- --
--   >>> traverse id [Right 1, Right 2, Right 3, Right 4]
--   Right [1,2,3,4]
--   
-- -- In the next examples, we show that Nothing and Left -- values short circuit the created structure. -- --
--   >>> traverse (const Nothing) [1,2,3,4]
--   Nothing
--   
-- --
--   >>> traverse (\x -> if odd x then Just x else Nothing)  [1,2,3,4]
--   Nothing
--   
-- --
--   >>> traverse id [Right 1, Right 2, Right 3, Right 4, Left 0]
--   Left 0
--   
traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) -- | Evaluate each action in the structure from left to right, and collect -- the results. For a version that ignores the results see -- sequenceA_. -- --

Examples

-- -- Basic usage: -- -- For the first two examples we show sequenceA fully evaluating a a -- structure and collecting the results. -- --
--   >>> sequenceA [Just 1, Just 2, Just 3]
--   Just [1,2,3]
--   
-- --
--   >>> sequenceA [Right 1, Right 2, Right 3]
--   Right [1,2,3]
--   
-- -- The next two example show Nothing and Just will short -- circuit the resulting structure if present in the input. For more -- context, check the Traversable instances for Either and -- Maybe. -- --
--   >>> sequenceA [Just 1, Just 2, Just 3, Nothing]
--   Nothing
--   
-- --
--   >>> sequenceA [Right 1, Right 2, Right 3, Left 4]
--   Left 4
--   
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_. -- --

Examples

-- -- mapM is literally a traverse with a type signature -- restricted to Monad. Its implementation may be more efficient -- due to additional power of Monad. 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_. -- --

Examples

-- -- Basic usage: -- -- The first two examples are instances where the input and and output of -- sequence are isomorphic. -- --
--   >>> sequence $ Right [1,2,3,4]
--   [Right 1,Right 2,Right 3,Right 4]
--   
-- --
--   >>> sequence $ [Right 1,Right 2,Right 3,Right 4]
--   Right [1,2,3,4]
--   
-- -- The following examples demonstrate short circuit behavior for -- sequence. -- --
--   >>> sequence $ Left [1,2,3,4]
--   Left [1,2,3,4]
--   
-- --
--   >>> sequence $ [Left 0, Right 1,Right 2,Right 3,Right 4]
--   Left 0
--   
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) -- | Identity function. -- --
--   id x = x
--   
-- -- This function might seem useless at first glance, but it can be very -- useful in a higher order context. -- --

Examples

-- --
--   >>> length $ filter id [True, True, False, True]
--   3
--   
-- --
--   >>> Just (Just 3) >>= id
--   Just 3
--   
-- --
--   >>> foldr id 0 [(^3), (*5), (+2)]
--   1000
--   
id :: a -> a -- | const x y always evaluates to x, ignoring its second -- argument. -- --
--   const x = \_ -> x
--   
-- -- This function might seem useless at first glance, but it can be very -- useful in a higher order context. -- --

Examples

-- --
--   >>> const 42 "hello"
--   42
--   
-- --
--   >>> map (const 42) [0..3]
--   [42,42,42,42]
--   
const :: a -> b -> a -- | Right to left function composition. -- --
--   (f . g) x = f (g x)
--   
-- --
--   f . id = f = id . f
--   
-- --

Examples

-- --
--   >>> map ((*2) . length) [[], [0, 1, 2], [0]]
--   [0,6,2]
--   
-- --
--   >>> foldr (.) id [(+1), (*3), (^3)] 2
--   25
--   
-- --
--   >>> let (...) = (.).(.) in ((*2)...(+)) 5 10
--   30
--   
(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | flip f takes its (first) two arguments in the reverse -- order of f. -- --
--   flip f x y = f y x
--   
-- --
--   flip . flip = id
--   
-- --

Examples

-- --
--   >>> flip (++) "hello" "world"
--   "worldhello"
--   
-- --
--   >>> let (.>) = flip (.) in (+1) .> show $ 5
--   "6"
--   
flip :: (a -> b -> c) -> b -> a -> c -- | ($) is the function application operator. -- -- Applying ($) to a function f and an argument -- x gives the same result as applying f to x -- directly. The definition is akin to this: -- --
--   ($) :: (a -> b) -> a -> b
--   ($) f x = f x
--   
-- -- This is id specialized from a -> a to -- (a -> b) -> (a -> b) which by the associativity of -- (->) is the same as (a -> b) -> a -> b. -- -- On the face of it, this may appear pointless! But it's actually one of -- the most useful and important operators in Haskell. -- -- The order of operations is very different between ($) and -- normal function application. Normal function application has -- precedence 10 - higher than any operator - and associates to the left. -- So these two definitions are equivalent: -- --
--   expr = min 5 1 + 5
--   expr = ((min 5) 1) + 5
--   
-- -- ($) has precedence 0 (the lowest) and associates to the -- right, so these are equivalent: -- --
--   expr = min 5 $ 1 + 5
--   expr = (min 5) (1 + 5)
--   
-- --

Examples

-- -- A common use cases of ($) is to avoid parentheses in complex -- expressions. -- -- For example, instead of using nested parentheses in the following -- Haskell function: -- --
--   -- | Sum numbers in a string: strSum "100  5 -7" == 98
--   strSum :: String -> Int
--   strSum s = sum (mapMaybe readMaybe (words s))
--   
-- -- we can deploy the function application operator: -- --
--   -- | Sum numbers in a string: strSum "100  5 -7" == 98
--   strSum :: String -> Int
--   strSum s = sum $ mapMaybe readMaybe $ words s
--   
-- -- ($) is also used as a section (a partially applied operator), -- in order to indicate that we wish to apply some yet-unspecified -- function to a given value. For example, to apply the argument -- 5 to a list of functions: -- --
--   applyFive :: [Int]
--   applyFive = map ($ 5) [(+1), (2^)]
--   >>> [6, 32]
--   
-- --

Technical Remark (Representation Polymorphism)

-- -- ($) is fully representation-polymorphic. This allows it to -- also be used with arguments of unlifted and even unboxed kinds, such -- as unboxed integers: -- --
--   fastMod :: Int -> Int -> Int
--   fastMod (I# x) (I# m) = I# $ remInt# x m
--   
($) :: (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 :: HasCallStack => [Char] -> a -- | A variant of error that does not produce a stack trace. errorWithoutStackTrace :: [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 :: HasCallStack => a -- | The value of seq a b is bottom if a is -- bottom, and otherwise equal to b. In other words, it -- evaluates the first argument a to weak head normal form -- (WHNF). 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 infixr 0 `seq` -- | 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 $! -- | <math>. 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, ...]
--   
-- -- this means that map id == id -- --

Examples

-- --
--   >>> map (+1) [1, 2, 3]
--   [2,3,4]
--   
-- --
--   >>> map id [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> map (\n -> 3 * n + 1) [1, 2, 3]
--   [4,7,10]
--   
map :: (a -> b) -> [a] -> [b] -- | (++) appends 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. -- --

Performance considerations

-- -- This function takes linear time in the number of elements of the -- first list. Thus it is better to associate repeated -- applications of (++) to the right (which is the default -- behaviour): xs ++ (ys ++ zs) or simply xs ++ ys ++ -- zs, but not (xs ++ ys) ++ zs. For the same reason -- concat = foldr (++) [] has -- linear performance, while foldl (++) [] is -- prone to quadratic slowdown -- --

Examples

-- --
--   >>> [1, 2, 3] ++ [4, 5, 6]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> [] ++ [1, 2, 3]
--   [1,2,3]
--   
-- --
--   >>> [3, 2, 1] ++ []
--   [3,2,1]
--   
(++) :: [a] -> [a] -> [a] infixr 5 ++ -- | <math>. 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]
--   
-- --

Examples

-- --
--   >>> filter odd [1, 2, 3]
--   [1,3]
--   
-- --
--   >>> filter (\l -> length l > 3) ["Hello", ", ", "World", "!"]
--   ["Hello","World"]
--   
-- --
--   >>> filter (/= 3) [1, 2, 3, 4, 3, 2, 1]
--   [1,2,4,2,1]
--   
filter :: (a -> Bool) -> [a] -> [a] -- | <math>. Extract the first element of a list, which must be -- non-empty. -- --
Examples
-- --
--   >>> head [1, 2, 3]
--   1
--   
-- --
--   >>> head [1..]
--   1
--   
-- --
--   >>> head []
--   *** Exception: Prelude.head: empty list
--   
-- | Warning: This is a partial function, it throws an error on empty -- lists. Use pattern matching or Data.List.uncons instead. Consider -- refactoring to use Data.List.NonEmpty. head :: HasCallStack => [a] -> a -- | <math>. Extract the last element of a list, which must be finite -- and non-empty. -- -- WARNING: This function is partial. Consider using unsnoc -- instead. -- --

Examples

-- --
--   >>> last [1, 2, 3]
--   3
--   
-- --
--   >>> last [1..]
--   * Hangs forever *
--   
-- --
--   >>> last []
--   *** Exception: Prelude.last: empty list
--   
last :: HasCallStack => [a] -> a -- | <math>. Extract the elements after the head of a list, which -- must be non-empty. -- --

Examples

-- --
--   >>> tail [1, 2, 3]
--   [2,3]
--   
-- --
--   >>> tail [1]
--   []
--   
-- --
--   >>> tail []
--   *** Exception: Prelude.tail: empty list
--   
-- | Warning: This is a partial function, it throws an error on empty -- lists. Replace it with drop 1, or use pattern matching or -- Data.List.uncons instead. Consider refactoring to use -- Data.List.NonEmpty. tail :: HasCallStack => [a] -> [a] -- | <math>. Return all the elements of a list except the last one. -- The list must be non-empty. -- -- WARNING: This function is partial. Consider using unsnoc -- instead. -- --

Examples

-- --
--   >>> init [1, 2, 3]
--   [1,2]
--   
-- --
--   >>> init [1]
--   []
--   
-- --
--   >>> init []
--   *** Exception: Prelude.init: empty list
--   
init :: HasCallStack => [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. -- -- WARNING: This function is partial, and should only be used if you are -- sure that the indexing will not fail. Otherwise, use !?. -- -- WARNING: This function takes linear time in the index. -- --

Examples

-- --
--   >>> ['a', 'b', 'c'] !! 0
--   'a'
--   
-- --
--   >>> ['a', 'b', 'c'] !! 2
--   'c'
--   
-- --
--   >>> ['a', 'b', 'c'] !! 3
--   *** Exception: Prelude.!!: index too large
--   
-- --
--   >>> ['a', 'b', 'c'] !! (-1)
--   *** Exception: Prelude.!!: negative index
--   
(!!) :: HasCallStack => [a] -> Int -> a infixl 9 !! -- | Test whether the structure is empty. The default implementation is -- Left-associative and lazy in both the initial element and the -- accumulator. Thus optimised for structures where the first element can -- be accessed in constant time. Structures where this is not the case -- should have a non-default implementation. -- --

Examples

-- -- Basic usage: -- --
--   >>> null []
--   True
--   
-- --
--   >>> null [1]
--   False
--   
-- -- null is expected to terminate even for infinite structures. The -- default implementation terminates provided the structure is bounded on -- the left (there is a leftmost element). -- --
--   >>> null [1..]
--   False
--   
null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation just counts elements starting with the -- leftmost. Instances for structures that can compute the element count -- faster than via element-by-element counting, should provide a -- specialised implementation. -- --

Examples

-- -- Basic usage: -- --
--   >>> length []
--   0
--   
-- --
--   >>> length ['a', 'b', 'c']
--   3
--   
--   >>> length [1..]
--   * Hangs forever *
--   
length :: Foldable t => t a -> Int -- | <math>. reverse xs returns the elements of -- xs in reverse order. xs must be finite. -- --

Laziness

-- -- reverse is lazy in its elements. -- --
--   >>> head (reverse [undefined, 1])
--   1
--   
-- --
--   >>> reverse (1 : 2 : undefined)
--   *** Exception: Prelude.undefined
--   
-- --

Examples

-- --
--   >>> reverse []
--   []
--   
-- --
--   >>> reverse [42]
--   [42]
--   
-- --
--   >>> reverse [2,5,7]
--   [7,5,2]
--   
-- --
--   >>> reverse [1..]
--   * Hangs forever *
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> and []
--   True
--   
-- --
--   >>> and [True]
--   True
--   
-- --
--   >>> and [False]
--   False
--   
-- --
--   >>> and [True, True, False]
--   False
--   
-- --
--   >>> and (False : repeat True) -- Infinite list [False,True,True,True,...
--   False
--   
-- --
--   >>> and (repeat True)
--   * Hangs forever *
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> or []
--   False
--   
-- --
--   >>> or [True]
--   True
--   
-- --
--   >>> or [False]
--   False
--   
-- --
--   >>> or [True, True, False]
--   True
--   
-- --
--   >>> or (True : repeat False) -- Infinite list [True,False,False,False,...
--   True
--   
-- --
--   >>> or (repeat False)
--   * Hangs forever *
--   
or :: Foldable t => t Bool -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. -- --

Examples

-- -- Basic usage: -- --
--   >>> any (> 3) []
--   False
--   
-- --
--   >>> any (> 3) [1,2]
--   False
--   
-- --
--   >>> any (> 3) [1,2,3,4,5]
--   True
--   
-- --
--   >>> any (> 3) [1..]
--   True
--   
-- --
--   >>> any (> 3) [0, -1..]
--   * Hangs forever *
--   
any :: Foldable t => (a -> Bool) -> t a -> Bool -- | Determines whether all elements of the structure satisfy the -- predicate. -- --

Examples

-- -- Basic usage: -- --
--   >>> all (> 3) []
--   True
--   
-- --
--   >>> all (> 3) [1,2]
--   False
--   
-- --
--   >>> all (> 3) [1,2,3,4,5]
--   False
--   
-- --
--   >>> all (> 3) [1..]
--   False
--   
-- --
--   >>> all (> 3) [4..]
--   * Hangs forever *
--   
all :: Foldable t => (a -> Bool) -> t a -> Bool -- | The concatenation of all the elements of a container of lists. -- --

Examples

-- -- Basic usage: -- --
--   >>> concat (Just [1, 2, 3])
--   [1,2,3]
--   
-- --
--   >>> concat (Left 42)
--   []
--   
-- --
--   >>> concat [[1, 2, 3], [4, 5], [6], []]
--   [1,2,3,4,5,6]
--   
concat :: Foldable t => t [a] -> [a] -- | Map a function over all the elements of a container and concatenate -- the resulting lists. -- --

Examples

-- -- Basic usage: -- --
--   >>> concatMap (take 3) [[1..], [10..], [100..], [1000..]]
--   [1,2,3,10,11,12,100,101,102,1000,1001,1002]
--   
-- --
--   >>> concatMap (take 3) (Just [1..])
--   [1,2,3]
--   
concatMap :: Foldable t => (a -> [b]) -> t a -> [b] -- | <math>. 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
--   
-- --

Examples

-- --
--   >>> scanl (+) 0 [1..4]
--   [0,1,3,6,10]
--   
-- --
--   >>> scanl (+) 42 []
--   [42]
--   
-- --
--   >>> scanl (-) 100 [1..4]
--   [100,99,97,94,90]
--   
-- --
--   >>> scanl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   ["foo","afoo","bafoo","cbafoo","dcbafoo"]
--   
-- --
--   >>> take 10 (scanl (+) 0 [1..])
--   [0,1,3,6,10,15,21,28,36,45]
--   
-- --
--   >>> take 1 (scanl undefined 'a' undefined)
--   "a"
--   
scanl :: (b -> a -> b) -> b -> [a] -> [b] -- | <math>. scanl1 is a variant of scanl that has no -- starting value argument: -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
-- --

Examples

-- --
--   >>> scanl1 (+) [1..4]
--   [1,3,6,10]
--   
-- --
--   >>> scanl1 (+) []
--   []
--   
-- --
--   >>> scanl1 (-) [1..4]
--   [1,-1,-4,-8]
--   
-- --
--   >>> scanl1 (&&) [True, False, True, True]
--   [True,False,False,False]
--   
-- --
--   >>> scanl1 (||) [False, False, True, True]
--   [False,False,True,True]
--   
-- --
--   >>> take 10 (scanl1 (+) [1..])
--   [1,3,6,10,15,21,28,36,45,55]
--   
-- --
--   >>> take 1 (scanl1 undefined ('a' : undefined))
--   "a"
--   
scanl1 :: (a -> a -> a) -> [a] -> [a] -- | <math>. scanr is the right-to-left dual of scanl. -- Note that the order of parameters on the accumulating function are -- reversed compared to scanl. Also note that -- --
--   head (scanr f z xs) == foldr f z xs.
--   
-- --

Examples

-- --
--   >>> scanr (+) 0 [1..4]
--   [10,9,7,4,0]
--   
-- --
--   >>> scanr (+) 42 []
--   [42]
--   
-- --
--   >>> scanr (-) 100 [1..4]
--   [98,-97,99,-96,100]
--   
-- --
--   >>> scanr (\nextChar reversedString -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
--   ["abcdfoo","bcdfoo","cdfoo","dfoo","foo"]
--   
-- --
--   >>> force $ scanr (+) 0 [1..]
--   *** Exception: stack overflow
--   
scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | <math>. scanr1 is a variant of scanr that has no -- starting value argument. -- --

Examples

-- --
--   >>> scanr1 (+) [1..4]
--   [10,9,7,4]
--   
-- --
--   >>> scanr1 (+) []
--   []
--   
-- --
--   >>> scanr1 (-) [1..4]
--   [-2,3,-1,4]
--   
-- --
--   >>> scanr1 (&&) [True, False, True, True]
--   [False,False,True,True]
--   
-- --
--   >>> scanr1 (||) [True, True, False, False]
--   [True,True,False,False]
--   
-- --
--   >>> force $ scanr1 (+) [1..]
--   *** Exception: stack overflow
--   
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), ...]
--   
-- --

Laziness

-- -- Note that iterate is lazy, potentially leading to thunk -- build-up if the consumer doesn't force each iterate. See -- iterate' for a strict variant of this function. -- --
--   >>> take 1 $ iterate undefined 42
--   [42]
--   
-- --

Examples

-- --
--   >>> take 10 $ iterate not True
--   [True,False,True,False,True,False,True,False,True,False]
--   
-- --
--   >>> take 10 $ iterate (+3) 42
--   [42,45,48,51,54,57,60,63,66,69]
--   
-- -- iterate id == repeat: -- --
--   >>> take 10 $ iterate id 1
--   [1,1,1,1,1,1,1,1,1,1]
--   
iterate :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. -- --

Examples

-- --
--   >>> take 10 $ repeat 17
--   [17,17,17,17,17,17,17,17,17, 17]
--   
-- --
--   >>> repeat undefined
--   [*** Exception: Prelude.undefined
--   
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. -- --

Examples

-- --
--   >>> replicate 0 True
--   []
--   
-- --
--   >>> replicate (-1) True
--   []
--   
-- --
--   >>> replicate 4 True
--   [True,True,True,True]
--   
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. -- --

Examples

-- --
--   >>> cycle []
--   *** Exception: Prelude.cycle: empty list
--   
-- --
--   >>> take 10 (cycle [42])
--   [42,42,42,42,42,42,42,42,42,42]
--   
-- --
--   >>> take 10 (cycle [2, 5, 7])
--   [2,5,7,2,5,7,2,5,7,2]
--   
-- --
--   >>> take 1 (cycle (42 : undefined))
--   [42]
--   
cycle :: HasCallStack => [a] -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n >= length xs. -- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. -- --

Laziness

-- --
--   >>> take 0 undefined
--   []
--   
--   >>> take 2 (1 : 2 : undefined)
--   [1,2]
--   
-- --

Examples

-- --
--   >>> 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]
--   []
--   
take :: Int -> [a] -> [a] -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n >= length -- xs. -- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. -- --

Examples

-- --
--   >>> 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]
--   
drop :: Int -> [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. -- --

Laziness

-- --
--   >>> takeWhile (const False) undefined
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> takeWhile (const False) (undefined : undefined)
--   []
--   
-- --
--   >>> take 1 (takeWhile (const True) (1 : undefined))
--   [1]
--   
-- --

Examples

-- --
--   >>> 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. -- --

Examples

-- --
--   >>> 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 the longest prefix (possibly -- empty) of xs of elements that satisfy p and second -- element is the remainder of the list: -- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs), even if p is _|_. -- --

Laziness

-- --
--   >>> span undefined []
--   ([],[])
--   
--   >>> fst (span (const False) undefined)
--   *** Exception: Prelude.undefined
--   
--   >>> fst (span (const False) (undefined : undefined))
--   []
--   
--   >>> take 1 (fst (span (const True) (1 : undefined)))
--   [1]
--   
-- -- span produces the first component of the tuple lazily: -- --
--   >>> take 10 (fst (span (const True) [1..]))
--   [1,2,3,4,5,6,7,8,9,10]
--   
-- --

Examples

-- --
--   >>> 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 :: (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 p is equivalent to span (not . -- p) and consequently to (takeWhile (not . p) xs, -- dropWhile (not . p) xs), even if p is -- _|_. -- --

Laziness

-- --
--   >>> break undefined []
--   ([],[])
--   
-- --
--   >>> fst (break (const True) undefined)
--   *** Exception: Prelude.undefined
--   
-- --
--   >>> fst (break (const True) (undefined : undefined))
--   []
--   
-- --
--   >>> take 1 (fst (break (const False) (1 : undefined)))
--   [1]
--   
-- -- break produces the first component of the tuple lazily: -- --
--   >>> take 10 (fst (break (const False) [1..]))
--   [1,2,3,4,5,6,7,8,9,10]
--   
-- --

Examples

-- --
--   >>> 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 :: (a -> Bool) -> [a] -> ([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 is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. -- --

Laziness

-- -- It is equivalent to (take n xs, drop n xs) -- unless n is _|_: splitAt _|_ xs = _|_, not -- (_|_, _|_)). -- -- The first component of the tuple is produced lazily: -- --
--   >>> fst (splitAt 0 undefined)
--   []
--   
-- --
--   >>> take 1 (fst (splitAt 10 (1 : undefined)))
--   [1]
--   
-- --

Examples

-- --
--   >>> 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])
--   
splitAt :: Int -> [a] -> ([a], [a]) -- | notElem is the negation of elem. -- --

Examples

-- -- Basic usage: -- --
--   >>> 3 `notElem` []
--   True
--   
-- --
--   >>> 3 `notElem` [1,2]
--   True
--   
-- --
--   >>> 3 `notElem` [1,2,3,4,5]
--   False
--   
-- -- For infinite structures, notElem terminates if the value exists -- at a finite distance from the left side of the structure: -- --
--   >>> 3 `notElem` [1..]
--   False
--   
-- --
--   >>> 3 `notElem` ([4..] ++ [3])
--   * Hangs forever *
--   
notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `notElem` -- | <math>. lookup key assocs looks up a key in an -- association list. For the result to be Nothing, the list must -- be finite. -- --

Examples

-- --
--   >>> lookup 2 []
--   Nothing
--   
-- --
--   >>> lookup 2 [(1, "first")]
--   Nothing
--   
-- --
--   >>> lookup 2 [(1, "first"), (2, "second"), (3, "third")]
--   Just "second"
--   
lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | <math>. zip takes two lists and returns a list of -- corresponding pairs. -- -- zip is right-lazy: -- --
--   >>> zip [] undefined
--   []
--   
--   >>> zip undefined []
--   *** Exception: Prelude.undefined
--   ...
--   
-- -- zip is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. -- --

Examples

-- --
--   >>> zip [1, 2, 3] ['a', 'b', 'c']
--   [(1,'a'),(2,'b'),(3,'c')]
--   
-- -- If one input list is shorter than the other, excess elements of the -- longer list are discarded, even if one of the lists is infinite: -- --
--   >>> zip [1] ['a', 'b']
--   [(1,'a')]
--   
-- --
--   >>> zip [1, 2] ['a']
--   [(1,'a')]
--   
-- --
--   >>> zip [] [1..]
--   []
--   
-- --
--   >>> zip [1..] []
--   []
--   
zip :: [a] -> [b] -> [(a, b)] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. It is capable of list fusion, but it is restricted to -- its first list argument and its resulting list. zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] -- | <math>. zipWith generalises zip by zipping with -- the function given as the first argument, instead of a tupling -- function. -- --
--   zipWith (,) xs ys == zip xs ys
--   zipWith f [x1,x2,x3..] [y1,y2,y3..] == [f x1 y1, f x2 y2, f x3 y3..]
--   
-- -- zipWith is right-lazy: -- --
--   >>> let f = undefined
--   
--   >>> zipWith f [] undefined
--   []
--   
-- -- zipWith is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. -- --

Examples

-- -- zipWith (+) can be applied to two lists to -- produce the list of corresponding sums: -- --
--   >>> zipWith (+) [1, 2, 3] [4, 5, 6]
--   [5,7,9]
--   
-- --
--   >>> zipWith (++) ["hello ", "foo"] ["world!", "bar"]
--   ["hello world!","foobar"]
--   
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | <math>. The zipWith3 function takes a function which -- combines three elements, as well as three lists and returns a list of -- the function applied to corresponding elements, analogous to -- zipWith. It is capable of list fusion, but it is restricted to -- its first list argument and its resulting list. -- --
--   zipWith3 (,,) xs ys zs == zip3 xs ys zs
--   zipWith3 f [x1,x2,x3..] [y1,y2,y3..] [z1,z2,z3..] == [f x1 y1 z1, f x2 y2 z2, f x3 y3 z3..]
--   
-- --

Examples

-- --
--   >>> zipWith3 (\x y z -> [x, y, z]) "123" "abc" "xyz"
--   ["1ax","2by","3cz"]
--   
-- --
--   >>> zipWith3 (\x y z -> (x * y) + z) [1, 2, 3] [4, 5, 6] [7, 8, 9]
--   [11,18,27]
--   
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. -- --

Examples

-- --
--   >>> unzip []
--   ([],[])
--   
-- --
--   >>> unzip [(1, 'a'), (2, 'b')]
--   ([1,2],"ab")
--   
unzip :: [(a, b)] -> ([a], [b]) -- | The unzip3 function takes a list of triples and returns three -- lists of the respective components, analogous to unzip. -- --

Examples

-- --
--   >>> unzip3 []
--   ([],[],[])
--   
-- --
--   >>> unzip3 [(1, 'a', True), (2, 'b', False)]
--   ([1,2],"ab",[True,False])
--   
unzip3 :: [(a, b, c)] -> ([a], [b], [c]) -- | Splits the argument into a list of lines stripped of their -- terminating \n characters. The \n terminator is -- optional in a final non-empty line of the argument string. -- -- When the argument string is empty, or ends in a \n character, -- it can be recovered by passing the result of lines to the -- unlines function. Otherwise, unlines appends the missing -- terminating \n. This makes unlines . lines -- idempotent: -- --
--   (unlines . lines) . (unlines . lines) = (unlines . lines)
--   
-- --

Examples

-- --
--   >>> lines ""           -- empty input contains no lines
--   []
--   
-- --
--   >>> lines "\n"         -- single empty line
--   [""]
--   
-- --
--   >>> lines "one"        -- single unterminated line
--   ["one"]
--   
-- --
--   >>> lines "one\n"      -- single non-empty line
--   ["one"]
--   
-- --
--   >>> lines "one\n\n"    -- second line is empty
--   ["one",""]
--   
-- --
--   >>> lines "one\ntwo"   -- second line is unterminated
--   ["one","two"]
--   
-- --
--   >>> lines "one\ntwo\n" -- two non-empty lines
--   ["one","two"]
--   
lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space (as defined by isSpace). This function -- trims any white spaces at the beginning and at the end. -- --

Examples

-- --
--   >>> words "Lorem ipsum\ndolor"
--   ["Lorem","ipsum","dolor"]
--   
-- --
--   >>> words " foo bar "
--   ["foo","bar"]
--   
words :: String -> [String] -- | Appends a \n character to each input string, then -- concatenates the results. Equivalent to foldMap (s -> -- s ++ "\n"). -- --

Examples

-- --
--   >>> unlines ["Hello", "World", "!"]
--   "Hello\nWorld\n!\n"
--   
-- -- Note that unlines . lines /= -- id when the input is not \n-terminated: -- --
--   >>> unlines . lines $ "foo\nbar"
--   "foo\nbar\n"
--   
unlines :: [String] -> String -- | unwords joins words with separating spaces (U+0020 SPACE). -- -- unwords is neither left nor right inverse of words: -- --
--   >>> words (unwords [" "])
--   []
--   
--   >>> unwords (words "foo\nbar")
--   "foo bar"
--   
-- --

Examples

-- --
--   >>> unwords ["Lorem", "ipsum", "dolor"]
--   "Lorem ipsum dolor"
--   
-- --
--   >>> unwords ["foo", "bar", "", "baz"]
--   "foo bar  baz"
--   
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 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 fails with an -- error if the parse is unsuccessful, and it is therefore -- discouraged from being used in real applications. Use readMaybe -- or readEither for safe alternatives. -- --
--   >>> read "123" :: Int
--   123
--   
-- --
--   >>> read "hello" :: Int
--   *** Exception: Prelude.read: no parse
--   
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 -- | Lifted, homogeneous equality. By lifted, we mean that it can be bogus -- (deferred type error). By homogeneous, the two types a and -- b must have the same kinds. class a ~# b => (a :: k) ~ (b :: k) infix 4 ~ -- | 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 -- | TypeRep is a concrete representation of a (monomorphic) type. -- TypeRep supports reasonably efficient equality. See Note [Grand -- plan for Typeable] in GHC.Tc.Instance.Typeable data TypeRep (a :: k) -- | Construct a representation for a type application. mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep a -> TypeRep b -> TypeRep (a b) -- | Exquisitely unsafe. mkTyCon :: String -> String -> String -> Int -> KindRep -> TyCon -- | Observe the Fingerprint of a type representation typeRepFingerprint :: forall {k} (a :: k). 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 pattern KindRepTypeLit :: TypeLitSort -> String -> KindRep data TypeLitSort TypeLitSymbol :: TypeLitSort TypeLitNat :: TypeLitSort TypeLitChar :: 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. -- --
--   >>> printf "%s, %d, %.4f" "hello" 123 pi
--   hello, 123, 3.1416
--   
-- -- 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: -- -- 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.PrintfArg a, Text.Printf.HPrintfType r) => Text.Printf.HPrintfType (a -> r) instance (a GHC.Types.~ ()) => Text.Printf.HPrintfType (GHC.Types.IO a) instance Text.Printf.IsChar GHC.Types.Char instance Text.Printf.PrintfArg GHC.Types.Char instance Text.Printf.PrintfArg GHC.Types.Double instance Text.Printf.PrintfArg GHC.Types.Float instance Text.Printf.PrintfArg GHC.Types.Int 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.Int.Int8 instance Text.Printf.PrintfArg GHC.Num.Integer.Integer instance Text.Printf.IsChar c => Text.Printf.PrintfArg [c] instance Text.Printf.PrintfArg GHC.Num.Natural.Natural instance Text.Printf.PrintfArg GHC.Types.Word 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.Word.Word8 instance (Text.Printf.PrintfArg a, Text.Printf.PrintfType r) => Text.Printf.PrintfType (a -> r) instance (a GHC.Types.~ ()) => Text.Printf.PrintfType (GHC.Types.IO a) instance Text.Printf.IsChar c => Text.Printf.PrintfType [c] -- | 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 resurrect 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, MVar, -- and TVar. However, to place a finalizer on one of these -- types, you should use the specific operation provided for that type, -- e.g. mkWeakIORef, mkWeakMVar and mkWeakTVar -- respectively. 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)) -- | Set the global action called to report exceptions thrown by weak -- pointer finalizers to the user. setFinalizerExceptionHandler :: (SomeException -> IO ()) -> IO () -- | Get the global action called to report exceptions thrown by weak -- pointer finalizers to the user. getFinalizerExceptionHandler :: IO (SomeException -> IO ()) -- | An exception handler for Handle finalization that prints the -- error to the given Handle, but doesn't rethrow it. printToHandleFinalizerExceptionHandler :: Handle -> SomeException -> IO () -- | 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. -- -- For a comprehensive listing of supported platforms, please refer to -- https://gitlab.haskell.org/ghc/ghc/-/wikis/platforms module System.Info -- | The operating system on which the program is running. Common values -- include: -- -- os :: String -- | The machine architecture on which the program is running. Common -- values include: -- -- arch :: String -- | The Haskell implementation with which the program was compiled or is -- being interpreted. On the GHC platform, the value is "ghc". compilerName :: String -- | The version of compilerName with which the program was compiled -- or is being interpreted. -- --

Example

-- --
--   ghci> compilerVersion
--   Version {versionBranch = [8,8], versionTags = []}
--   
compilerVersion :: Version -- | The full version of compilerName with which the program was -- compiled or is being interpreted. It includes the major, minor, -- revision and an additional identifier, generally in the form -- "yearmonthday". fullCompilerVersion :: 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 an Exception, it 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 ExitCode 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 -- | Get an action to query the absolute pathname of the current -- executable. -- -- If the operating system provides a reliable way to determine the -- current executable, return the query action, otherwise return -- Nothing. The action is defined on FreeBSD, Linux, MacOS, -- NetBSD, Solaris, and Windows. -- -- Even where the query action is defined, there may be situations where -- no result is available, e.g. if the executable file was deleted while -- the program is running. Therefore the result of the query action is a -- Maybe FilePath. -- -- Note that for scripts and interactive sessions, the result is the path -- to the interpreter (e.g. ghci.) -- -- Note also that while most operating systems return Nothing if -- the executable file was deleted/unlinked, some (including NetBSD) -- return the original path. executablePath :: Maybe (IO (Maybe FilePath)) -- | Returns the absolute pathname of the current executable, or -- argv[0] if the operating system does not provide a reliable -- way query the current executable. -- -- Note that for scripts and interactive sessions, this is the path to -- the interpreter (e.g. ghci.) -- -- Since base 4.11.0.0, getExecutablePath resolves symlinks on -- Windows. If an executable is launched through a symlink, -- getExecutablePath returns the absolute path of the original -- executable. -- -- If the executable has been deleted, behaviour is ill-defined and -- varies by operating system. See executablePath for a more -- reliable way to query the current executable. getExecutablePath :: IO FilePath -- | Computation getEnv var returns the value of the -- environment variable var. For the inverse, the setEnv -- function can be used. -- -- 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. -- -- Early versions of this function operated under the mistaken belief -- that setting an environment variable to the empty string on -- Windows removes that environment variable from the environment. For -- the sake of compatibility, it adopted that behavior on POSIX. In -- particular -- --
--   setEnv name ""
--   
-- -- has the same effect as -- --
--   unsetEnv name
--   
-- -- If you'd like to be able to set environment variables to blank -- strings, use setEnv. -- -- 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)] -- | A setEnv implementation that allows blank environment variables. -- Mimics the Env module from the unix package, but with -- support for Windows too. -- -- The matrix of platforms that: -- -- -- -- is very complicated. Some platforms don't support unsetting of -- environment variables at all. module System.Environment.Blank -- | 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, or -- argv[0] if the operating system does not provide a reliable -- way query the current executable. -- -- Note that for scripts and interactive sessions, this is the path to -- the interpreter (e.g. ghci.) -- -- Since base 4.11.0.0, getExecutablePath resolves symlinks on -- Windows. If an executable is launched through a symlink, -- getExecutablePath returns the absolute path of the original -- executable. -- -- If the executable has been deleted, behaviour is ill-defined and -- varies by operating system. See executablePath for a more -- reliable way to query the current executable. getExecutablePath :: IO FilePath -- | 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)] -- | Similar to lookupEnv. getEnv :: String -> IO (Maybe String) -- | Get an environment value or a default value. getEnvDefault :: String -> String -> IO String -- | Like setEnv, but allows blank environment values and mimics the -- function signature of setEnv from the unix package. setEnv :: String -> String -> Bool -> IO () -- | Like unsetEnv, but allows for the removal of blank environment -- variables. May throw an exception if the underlying platform doesn't -- support unsetting of environment variables. unsetEnv :: String -> IO () -- | 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.ArgDescr instance GHC.Base.Functor System.Console.GetOpt.ArgOrder instance GHC.Base.Functor System.Console.GetOpt.OptDescr -- | 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 -- | 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. -- -- The various communicating processes need to agree on the keys used to -- refer to the values in the Static Pointer Table, or lookups will fail. -- Only processes launched from the same program binary are guaranteed to -- use the same set of keys. 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)) -- | Miscellaneous 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. -- -- GHC wraps each use of the static keyword with -- fromStaticPtr. Because the static keyword requires its -- argument to be an instance of Typeable, fromStaticPtr -- carries a Typeable constraint as well. class IsStatic (p :: Type -> Type) fromStaticPtr :: (IsStatic p, Typeable a) => StaticPtr a -> p a instance GHC.StaticPtr.IsStatic GHC.StaticPtr.StaticPtr instance GHC.Show.Show GHC.StaticPtr.StaticPtrInfo -- | Stable names are a way of performing fast ( <math> ), -- 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 GHC.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 StableName :: StableName# a -> 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 (GHC.StableName.StableName a) -- | Stable names are a way of performing fast ( <math> ), -- 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 -- | GCC style response files. module GHC.ResponseFile -- | Like getArgs, but can also read arguments supplied via response -- files. -- -- For example, consider a program foo: -- --
--   main :: IO ()
--   main = do
--     args <- getArgsWithResponseFiles
--     putStrLn (show args)
--   
-- -- And a response file args.txt: -- --
--   --one 1
--   --'two' 2
--   --"three" 3
--   
-- -- Then the result of invoking foo with args.txt is: -- --
--   > ./foo @args.txt
--   ["--one","1","--two","2","--three","3"]
--   
getArgsWithResponseFiles :: IO [String] -- | Given a string of concatenated strings, separate each by removing a -- layer of quoting and/or escaping of certain characters. -- -- These characters are: any whitespace, single quote, double quote, and -- the backslash character. The backslash character always escapes (i.e., -- passes through without further consideration) the character which -- follows. Characters can also be escaped in blocks by quoting (i.e., -- surrounding the blocks with matching pairs of either single- or -- double-quotes which are not themselves escaped). -- -- Any whitespace which appears outside of either of the quoting and -- escaping mechanisms, is interpreted as having been added by this -- special concatenation process to designate where the boundaries are -- between the original, un-concatenated list of strings. These added -- whitespace characters are removed from the output. -- --
--   unescapeArgs "hello\\ \\\"world\\\"\n" == ["hello \"world\""]
--   
unescapeArgs :: String -> [String] -- | Given a list of strings, concatenate them into a single string with -- escaping of certain characters, and the addition of a newline between -- each string. The escaping is done by adding a single backslash -- character before any whitespace, single quote, double quote, or -- backslash character, so this escaping character must be removed. -- Unescaped whitespace (in this case, newline) is part of this -- "transport" format to indicate the end of the previous string and the -- start of a new string. -- -- While unescapeArgs allows using quoting (i.e., convenient -- escaping of many characters) by having matching sets of single- or -- double-quotes,escapeArgs does not use the quoting mechanism, -- and thus will always escape any whitespace, quotes, and backslashes. -- --
--   escapeArgs ["hello \"world\""] == "hello\\ \\\"world\\\"\n"
--   
escapeArgs :: [String] -> String -- | Arguments which look like @foo will be replaced with the -- contents of file foo. A gcc-like syntax for response files -- arguments is expected. This must re-constitute the argument list by -- doing an inverse of the escaping mechanism done by the calling-program -- side. -- -- We quit if the file is not found or reading somehow fails. (A -- convenience routine for haddock or possibly other clients) expandResponse :: [String] -> IO [String] -- | This module defines the HasField class used by the -- OverloadedRecordFields extension. See the -- <https://gitlab.haskell.org/ghc/ghc/wikis/records/overloaded-record-fields -- 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 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 -- | Various helpers used by the GHCi shell. module GHC.GHCi.Helpers disableBuffering :: IO () flushAll :: IO () evalWrapper :: String -> [String] -> IO a -> IO a -- | Target byte ordering. module GHC.ByteOrder -- | Byte ordering. data ByteOrder -- | most-significant-byte occurs in lowest address. BigEndian :: ByteOrder -- | least-significant-byte occurs in lowest address. LittleEndian :: ByteOrder -- | The byte ordering of the target machine. targetByteOrder :: ByteOrder instance GHC.Enum.Bounded GHC.ByteOrder.ByteOrder instance GHC.Enum.Enum GHC.ByteOrder.ByteOrder instance GHC.Classes.Eq GHC.ByteOrder.ByteOrder instance GHC.Generics.Generic GHC.ByteOrder.ByteOrder instance GHC.Classes.Ord GHC.ByteOrder.ByteOrder instance GHC.Read.Read GHC.ByteOrder.ByteOrder instance GHC.Show.Show GHC.ByteOrder.ByteOrder -- | 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". -- --
--   >>> let x :: Either Void Int; x = Right 5
--   
--   >>> :{
--   case x of
--       Right r -> r
--       Left l  -> absurd l
--   :}
--   5
--   
absurd :: Void -> a -- | If Void is uninhabited then any Functor that holds only -- values of type Void is holding no values. It is implemented in -- terms of fmap absurd. vacuous :: Functor f => f Void -> f 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. -- --
--   >>> :{
--   do x <- newUnique
--      print (x == x)
--      y <- newUnique
--      print (x == y)
--   :}
--   True
--   False
--   
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.Eq Data.Unique.Unique instance GHC.Classes.Ord 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 -- --
--   >>> :{
--   runST (do
--       ref <- newSTRef "hello"
--       x <- readSTRef ref
--       writeSTRef ref (x ++ "world")
--       readSTRef ref )
--   :}
--   "helloworld"
--   
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. -- --
--   >>> :{
--   runST (do
--       ref <- newSTRef ""
--       modifySTRef ref (const "world")
--       modifySTRef ref (++ "!")
--       modifySTRef ref ("Hello, " ++)
--       readSTRef ref )
--   :}
--   "Hello, world!"
--   
-- -- Be warned that modifySTRef does not apply the function -- strictly. This means if the program calls modifySTRef many -- times, but seldom uses the value, thunks will pile up in memory -- resulting in a space leak. This is a common mistake made when using an -- STRef as a counter. For example, the following will leak memory -- and may produce a stack overflow: -- --
--   >>> import Control.Monad (replicateM_)
--   
--   >>> :{
--   print (runST (do
--       ref <- newSTRef 0
--       replicateM_ 1000 $ modifySTRef ref (+1)
--       readSTRef ref ))
--   :}
--   1000
--   
-- -- 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. -- -- Note that Ratio's instances inherit the deficiencies from the -- type parameter's. For example, Ratio Natural's Num -- instance has similar problems to Natural's. 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 lifted values. For example Int :: -- Type. type Type = TYPE LiftedRep -- | The kind of lifted constraints type Constraint = CONSTRAINT LiftedRep -- | The builtin function type, written in infix form as a % m -> -- b. Values of this type are functions taking inputs of type -- a and producing outputs of type b. The multiplicity -- of the input is m. -- -- Note that FUN m a b permits representation -- polymorphism in both a and b, so that types like -- Int# -> Int# can still be well-kinded. data FUN -- | 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 state thread type parameter. 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 state thread type parameter. -- -- 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 ST monad. The ST monad allows for destructive -- updates, but is escapable (unlike IO). A computation of type -- ST s a returns a value of type a, and execute -- in "thread" s. 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 thread. 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 an ST 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 thread 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 ST monad. The ST monad allows for destructive -- updates, but is escapable (unlike IO). A computation of type -- ST s a returns a value of type a, and execute -- in "thread" s. 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 thread. 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 an ST 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 thread 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 -- ST 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 -- ST 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 ST monad. The ST monad allows for destructive -- updates, but is escapable (unlike IO). A computation of type -- ST s a returns a value of type a, and -- executes in "thread" s. 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 an ST 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 an ST 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 ST 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 ST monad. The ST monad allows for destructive -- updates, but is escapable (unlike IO). A computation of type -- ST s a returns a value of type a, and -- executes in "thread" s. 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 an ST 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 an ST 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 ST 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 -- --
--   >>> :{
--   runST (do
--       ref <- newSTRef "hello"
--       x <- readSTRef ref
--       writeSTRef ref (x ++ "world")
--       readSTRef ref )
--   :}
--   "helloworld"
--   
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 -- | A type f is a Functor if it provides a function fmap -- which, given any types a and b lets you apply any -- function from (a -> b) to turn an f a into an -- f b, preserving the structure of f. Furthermore -- f needs to adhere to the following: -- -- -- -- Note, that the second law follows from the free theorem of the type -- fmap and the first law, so you need only check that the former -- condition holds. See -- https://www.schoolofhaskell.com/user/edwardk/snippets/fmap or -- https://github.com/quchen/articles/blob/master/second_functor_law.md -- for an explanation. class Functor (f :: Type -> Type) -- | fmap is used to apply a function of type (a -> b) -- to a value of type f a, where f is a functor, to produce a -- value of type f b. Note that for any type constructor with -- more than one parameter (e.g., Either), only the last type -- parameter can be modified with fmap (e.g., b in -- `Either a b`). -- -- Some type constructors with two parameters or more have a -- Bifunctor instance that allows both the last and the -- penultimate parameters to be mapped over. -- --

Examples

-- -- Convert from a Maybe Int to a Maybe String -- using show: -- --
--   >>> fmap show Nothing
--   Nothing
--   
--   >>> fmap show (Just 3)
--   Just "3"
--   
-- -- Convert from an Either Int Int to an Either Int -- String using show: -- --
--   >>> fmap show (Left 17)
--   Left 17
--   
--   >>> fmap show (Right 17)
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> fmap (*2) [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> fmap even (2,2)
--   (2,True)
--   
-- -- It may seem surprising that the function is only applied to the last -- element of the tuple compared to the list example above which applies -- it to every element in the list. To understand, remember that tuples -- are type constructors with multiple type parameters: a tuple of 3 -- elements (a,b,c) can also be written (,,) a b c and -- its Functor instance is defined for Functor ((,,) a -- b) (i.e., only the third parameter is free to be mapped over with -- fmap). -- -- It explains why fmap can be used with tuples containing -- values of different types as in the following example: -- --
--   >>> fmap even ("hello", 1.0, 4)
--   ("hello",1.0,True)
--   
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. -- --

Examples

-- -- Perform a computation with Maybe and replace the result with a -- constant value if it is Just: -- --
--   >>> 'a' <$ Just 2
--   Just 'a'
--   
--   >>> 'a' <$ Nothing
--   Nothing
--   
(<$) :: Functor f => a -> f b -> f a infixl 4 <$ -- | 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: -- -- -- -- 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 :: Type -> Type) -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. -- -- 'as >>= bs' can be understood as the do -- expression -- --
--   do a <- as
--      bs a
--   
(>>=) :: 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. -- -- 'as >> bs' can be understood as the do -- expression -- --
--   do as
--      bs
--   
(>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a infixl 1 >>= infixl 1 >> -- | 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 :: Type -> Type) -- | Lift a computation from the IO monad. This allows us to run IO -- computations in any monadic stack, so long as it supports these kinds -- of operations (i.e. IO is the base monad for the stack). -- --

Example

-- --
--   import Control.Monad.Trans.State -- from the "transformers" library
--   
--   printState :: Show s => StateT s IO ()
--   printState = do
--     state <- get
--     liftIO $ print state
--   
-- -- Had we omitted liftIO, we would have ended up with -- this error: -- --
--   • Couldn't match type ‘IO’ with ‘StateT s IO’
--    Expected type: StateT s IO ()
--      Actual type: IO ()
--   
-- -- The important part here is the mismatch between StateT s IO -- () and IO (). -- -- Luckily, we know of a function that takes an IO a and -- returns an (m a): liftIO, enabling us to run -- the program and see the expected results: -- --
--   > evalStateT printState "hello"
--   "hello"
--   
--   > evalStateT printState 3
--   3
--   
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 -> Word64 -> RtsTime -> RtsTime -> RtsTime -> RtsTime -> RtsTime -> RtsTime -> RtsTime -> RtsTime -> 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) in the -- heap. Updated after a major GC. [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. Deprecated. [cumulative_par_max_copied_bytes] :: RTSStats -> Word64 -- | Sum of par_balanced_copied bytes across all parallel GCs [cumulative_par_balanced_copied_bytes] :: RTSStats -> Word64 -- | Total CPU time used by the init phase @since 4.12.0.0 [init_cpu_ns] :: RTSStats -> RtsTime -- | Total elapsed time used by the init phase @since 4.12.0.0 [init_elapsed_ns] :: RTSStats -> RtsTime -- | 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 -- | The total CPU time used during the post-mark pause phase of the -- concurrent nonmoving GC. [nonmoving_gc_sync_cpu_ns] :: RTSStats -> RtsTime -- | The total time elapsed during the post-mark pause phase of the -- concurrent nonmoving GC. [nonmoving_gc_sync_elapsed_ns] :: RTSStats -> RtsTime -- | The maximum elapsed length of any post-mark pause phase of the -- concurrent nonmoving GC. [nonmoving_gc_sync_max_elapsed_ns] :: RTSStats -> RtsTime -- | The total CPU time used by the nonmoving GC. [nonmoving_gc_cpu_ns] :: RTSStats -> RtsTime -- | The total time elapsed during which there is a nonmoving GC active. [nonmoving_gc_elapsed_ns] :: RTSStats -> RtsTime -- | The maximum time elapsed during any nonmoving GC cycle. [nonmoving_gc_max_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 -> Word64 -> Word64 -> RtsTime -> RtsTime -> 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 (includes large + compact data). -- Updated after every GC. Data in uncollected generations (in minor GCs) -- are considered live. [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. -- Deprecated. [gcdetails_par_max_copied_bytes] :: GCDetails -> Word64 -- | In parallel GC, the amount of balanced data copied by all threads [gcdetails_par_balanced_copied_bytes] :: GCDetails -> Word64 -- | The amount of memory lost due to block fragmentation in bytes. Block -- fragmentation is the difference between the amount of blocks retained -- by the RTS and the blocks that are in use. This occurs when megablocks -- are only sparsely used, eg, when data that cannot be moved retains a -- megablock. [gcdetails_block_fragmentation_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 -- | The CPU time used during the post-mark pause phase of the concurrent -- nonmoving GC. [gcdetails_nonmoving_gc_sync_cpu_ns] :: GCDetails -> RtsTime -- | The time elapsed during the post-mark pause phase of the concurrent -- nonmoving GC. [gcdetails_nonmoving_gc_sync_elapsed_ns] :: GCDetails -> RtsTime -- | Time values from the RTS, using a fixed resolution of nanoseconds. type RtsTime = Int64 -- | Get current runtime system statistics. getRTSStats :: IO RTSStats -- | Returns whether GC stats have been enabled (with +RTS -T, for -- example). getRTSStatsEnabled :: IO Bool instance GHC.Generics.Generic GHC.Stats.GCDetails instance GHC.Generics.Generic GHC.Stats.RTSStats instance GHC.Read.Read GHC.Stats.GCDetails instance GHC.Read.Read GHC.Stats.RTSStats instance GHC.Show.Show GHC.Stats.GCDetails instance GHC.Show.Show GHC.Stats.RTSStats -- | 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) -- | 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 infixr 5 :| -- | 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] -- | Construct a NonEmpty list from a single element. singleton :: a -> NonEmpty 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, starting with the shortest. The -- result is NonEmpty because the result always contains the empty -- list as the first element. -- --
--   inits [1,2,3] == [] :| [[1], [1,2], [1,2,3]]
--   inits [1] == [] :| [[1]]
--   inits [] == [] :| []
--   
inits :: Foldable f => f a -> NonEmpty [a] -- | The inits1 function takes a NonEmpty stream xs -- and returns all the NonEmpty finite prefixes of xs, -- starting with the shortest. -- --
--   inits1 (1 :| [2,3]) == (1 :| []) :| [1 :| [2], 1 :| [2,3]]
--   inits1 (1 :| []) == (1 :| []) :| []
--   
inits1 :: NonEmpty a -> NonEmpty (NonEmpty a) -- | The tails function takes a stream xs and returns all -- the suffixes of xs, starting with the longest. The result is -- NonEmpty because the result always contains the empty list as -- the last element. -- --
--   tails [1,2,3] == [1,2,3] :| [[2,3], [3], []]
--   tails [1] == [1] :| [[]]
--   tails [] == [] :| []
--   
tails :: Foldable f => f a -> NonEmpty [a] -- | The tails1 function takes a NonEmpty stream xs -- and returns all the non-empty suffixes of xs, starting with -- the longest. -- --
--   tails1 (1 :| [2,3]) == (1 :| [2,3]) :| [2 :| [3], 3 :| []]
--   tails1 (1 :| []) == (1 :| []) :| []
--   
tails1 :: NonEmpty a -> NonEmpty (NonEmpty a) -- | A monomorphic version of <> for NonEmpty. -- --
--   >>> append (1 :| []) (2 :| [3])
--   1 :| [2,3]
--   
append :: NonEmpty a -> NonEmpty a -> NonEmpty a -- | Attach a list at the end of a NonEmpty. -- --
--   >>> appendList (1 :| [2,3]) []
--   1 :| [2,3]
--   
-- --
--   >>> appendList (1 :| [2,3]) [4,5]
--   1 :| [2,3,4,5]
--   
appendList :: NonEmpty a -> [a] -> NonEmpty a -- | Attach a list at the beginning of a NonEmpty. -- --
--   >>> prependList [] (1 :| [2,3])
--   1 :| [2,3]
--   
-- --
--   >>> prependList [negate 1, 0] (1 :| [2, 3])
--   -1 :| [0,1,2,3]
--   
prependList :: [a] -> NonEmpty 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 isPrefixOf 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. (!!) :: HasCallStack => NonEmpty a -> Int -> a infixl 9 !! -- | 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 :: HasCallStack => [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 -- | Monadic zipping (used for monad comprehensions) module Control.Monad.Zip -- | Instances should satisfy the laws: -- -- class Monad m => MonadZip (m :: Type -> Type) 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 f, Control.Monad.Zip.MonadZip g) => Control.Monad.Zip.MonadZip (f GHC.Generics.:*: g) instance Control.Monad.Zip.MonadZip f => Control.Monad.Zip.MonadZip (Data.Semigroup.Internal.Alt f) instance Control.Monad.Zip.MonadZip Data.Ord.Down instance Control.Monad.Zip.MonadZip Data.Semigroup.Internal.Dual instance Control.Monad.Zip.MonadZip Data.Monoid.First instance Control.Monad.Zip.MonadZip Data.Functor.Identity.Identity instance Control.Monad.Zip.MonadZip Data.Monoid.Last instance Control.Monad.Zip.MonadZip [] instance Control.Monad.Zip.MonadZip f => Control.Monad.Zip.MonadZip (GHC.Generics.M1 i c f) instance Control.Monad.Zip.MonadZip GHC.Maybe.Maybe instance Control.Monad.Zip.MonadZip GHC.Base.NonEmpty instance Control.Monad.Zip.MonadZip GHC.Generics.Par1 instance Control.Monad.Zip.MonadZip Data.Semigroup.Internal.Product instance Control.Monad.Zip.MonadZip Data.Proxy.Proxy instance Control.Monad.Zip.MonadZip f => Control.Monad.Zip.MonadZip (GHC.Generics.Rec1 f) instance Control.Monad.Zip.MonadZip GHC.Tuple.Prim.Solo instance Control.Monad.Zip.MonadZip Data.Semigroup.Internal.Sum instance Control.Monad.Zip.MonadZip GHC.Generics.U1 module Data.Bifunctor -- | A bifunctor is a type constructor that takes two type arguments and is -- a functor in both arguments. That is, unlike with -- Functor, a type constructor such as Either does not need -- to be partially applied for a Bifunctor instance, and the -- methods in this class permit mapping functions over the Left -- value or the Right value, or both at the same time. -- -- 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. A partially applied -- Bifunctor must be a Functor and the second method -- must agree with fmap. From this it follows that: -- --
--   second id = id
--   
-- -- 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
--   
-- -- Since 4.18.0.0 Functor is a superclass of 'Bifunctor. class forall a. () => Functor p a => Bifunctor (p :: Type -> Type -> Type) -- | Map over both arguments at the same time. -- --
--   bimap f g ≡ first f . second g
--   
-- --

Examples

-- --
--   >>> bimap toUpper (+1) ('j', 3)
--   ('J',4)
--   
-- --
--   >>> bimap toUpper (+1) (Left 'j')
--   Left 'J'
--   
-- --
--   >>> bimap toUpper (+1) (Right 3)
--   Right 4
--   
bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d -- | Map covariantly over the first argument. -- --
--   first f ≡ bimap f id
--   
-- --

Examples

-- --
--   >>> first toUpper ('j', 3)
--   ('J',3)
--   
-- --
--   >>> first toUpper (Left 'j')
--   Left 'J'
--   
first :: Bifunctor p => (a -> b) -> p a c -> p b c -- | Map covariantly over the second argument. -- --
--   secondbimap id
--   
-- --

Examples

-- --
--   >>> second (+1) ('j', 3)
--   ('j',4)
--   
-- --
--   >>> second (+1) (Right 3)
--   Right 4
--   
second :: Bifunctor p => (b -> c) -> p a b -> p a c instance Data.Bifunctor.Bifunctor Data.Functor.Const.Const instance Data.Bifunctor.Bifunctor Data.Either.Either instance Data.Bifunctor.Bifunctor (GHC.Generics.K1 i) 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) 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)
--   
-- -- Some examples below also use the following BiList to showcase empty -- Bifoldable behaviors when relevant (Either and (,) -- containing always exactly resp. 1 and 2 elements): -- --
--   data BiList a b = BiList [a] [b]
--   
--   instance Bifoldable BiList where
--     bifoldr f g z (BiList as bs) = foldr f (foldr g z bs) as
--   
-- -- 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 :: Type -> Type -> Type) -- | Combines the elements of a structure using a monoid. -- --
--   bifoldbifoldMap id id
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> bifold (Right [1, 2, 3])
--   [1,2,3]
--   
-- --
--   >>> bifold (Left [5, 6])
--   [5,6]
--   
-- --
--   >>> bifold ([1, 2, 3], [4, 5])
--   [1,2,3,4,5]
--   
-- --
--   >>> bifold (Product 6, Product 7)
--   Product {getProduct = 42}
--   
-- --
--   >>> bifold (Sum 6, Sum 7)
--   Sum {getSum = 13}
--   
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
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> bifoldMap (take 3) (fmap digitToInt) ([1..], "89")
--   [1,2,3,8,9]
--   
-- --
--   >>> bifoldMap (take 3) (fmap digitToInt) (Left [1..])
--   [1,2,3]
--   
-- --
--   >>> bifoldMap (take 3) (fmap digitToInt) (Right "89")
--   [8,9]
--   
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
--   
-- --

Examples

-- -- Basic usage: -- --
--   > bifoldr (+) (*) 3 (5, 7)
--   26 -- 5 + (7 * 3)
--   
--   > bifoldr (+) (*) 3 (7, 5)
--   22 -- 7 + (5 * 3)
--   
--   > bifoldr (+) (*) 3 (Right 5)
--   15 -- 5 * 3
--   
--   > bifoldr (+) (*) 3 (Left 5)
--   8 -- 5 + 3
--   
bifoldr :: Bifoldable p => (a -> c -> c) -> (b -> c -> c) -> c -> p a b -> c -- | Combines the elements 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. -- --

Examples

-- -- Basic usage: -- --
--   > bifoldl (+) (*) 3 (5, 7)
--   56 -- (5 + 3) * 7
--   
--   > bifoldl (+) (*) 3 (7, 5)
--   50 -- (7 + 3) * 5
--   
--   > bifoldl (+) (*) 3 (Right 5)
--   15 -- 5 * 3
--   
--   > bifoldl (+) (*) 3 (Left 5)
--   8 -- 5 + 3
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bifoldr1 (+) (5, 7)
--   12
--   
-- --
--   >>> bifoldr1 (+) (Right 7)
--   7
--   
-- --
--   >>> bifoldr1 (+) (Left 5)
--   5
--   
-- --
--   > bifoldr1 (+) (BiList [1, 2] [3, 4])
--   10 -- 1 + (2 + (3 + 4))
--   
-- --
--   >>> bifoldr1 (+) (BiList [1, 2] [])
--   3
--   
-- -- On empty structures, this function throws an exception: -- --
--   >>> bifoldr1 (+) (BiList [] [])
--   *** Exception: bifoldr1: empty structure
--   ...
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bifoldl1 (+) (5, 7)
--   12
--   
-- --
--   >>> bifoldl1 (+) (Right 7)
--   7
--   
-- --
--   >>> bifoldl1 (+) (Left 5)
--   5
--   
-- --
--   > bifoldl1 (+) (BiList [1, 2] [3, 4])
--   10 -- ((1 + 2) + 3) + 4
--   
-- --
--   >>> bifoldl1 (+) (BiList [1, 2] [])
--   3
--   
-- -- On empty structures, this function throws an exception: -- --
--   >>> bifoldl1 (+) (BiList [] [])
--   *** Exception: bifoldl1: empty structure
--   ...
--   
bifoldl1 :: Bifoldable t => (a -> a -> a) -> t a a -> a -- | Left associative monadic bifold over a structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> bifoldlM (\a b -> print b >> pure a) (\a c -> print (show c) >> pure a) 42 ("Hello", True)
--   "Hello"
--   "True"
--   42
--   
-- --
--   >>> bifoldlM (\a b -> print b >> pure a) (\a c -> print (show c) >> pure a) 42 (Right True)
--   "True"
--   42
--   
-- --
--   >>> bifoldlM (\a b -> print b >> pure a) (\a c -> print (show c) >> pure a) 42 (Left "Hello")
--   "Hello"
--   42
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bitraverse_ print (print . show) ("Hello", True)
--   "Hello"
--   "True"
--   
-- --
--   >>> bitraverse_ print (print . show) (Right True)
--   "True"
--   
-- --
--   >>> bitraverse_ print (print . show) (Left "Hello")
--   "Hello"
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bifor_ ("Hello", True) print (print . show)
--   "Hello"
--   "True"
--   
-- --
--   >>> bifor_ (Right True) print (print . show)
--   "True"
--   
-- --
--   >>> bifor_ (Left "Hello") print (print . show)
--   "Hello"
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bisequence_ (print "Hello", print "World")
--   "Hello"
--   "World"
--   
-- --
--   >>> bisequence_ (Left (print "Hello"))
--   "Hello"
--   
-- --
--   >>> bisequence_ (Right (print "World"))
--   "World"
--   
bisequence_ :: (Bifoldable t, Applicative f) => t (f a) (f b) -> f () -- | The sum of a collection of actions, generalizing biconcat. -- --

Examples

-- -- Basic usage: -- --
--   >>> biasum (Nothing, Nothing)
--   Nothing
--   
-- --
--   >>> biasum (Nothing, Just 42)
--   Just 42
--   
-- --
--   >>> biasum (Just 18, Nothing)
--   Just 18
--   
-- --
--   >>> biasum (Just 18, Just 42)
--   Just 18
--   
biasum :: (Bifoldable t, Alternative f) => t (f a) (f a) -> f a -- | Collects the list of elements of a structure, from left to right. -- --

Examples

-- -- Basic usage: -- --
--   >>> biList (18, 42)
--   [18,42]
--   
-- --
--   >>> biList (Left 18)
--   [18]
--   
biList :: Bifoldable t => t a a -> [a] -- | Test whether the structure is empty. -- --

Examples

-- -- Basic usage: -- --
--   >>> binull (18, 42)
--   False
--   
-- --
--   >>> binull (Right 42)
--   False
--   
-- --
--   >>> binull (BiList [] [])
--   True
--   
binull :: Bifoldable t => t a b -> Bool -- | Returns the size/length of a finite structure as an Int. -- --

Examples

-- -- Basic usage: -- --
--   >>> bilength (True, 42)
--   2
--   
-- --
--   >>> bilength (Right 42)
--   1
--   
-- --
--   >>> bilength (BiList [1,2,3] [4,5])
--   5
--   
-- --
--   >>> bilength (BiList [] [])
--   0
--   
-- -- On infinite structures, this function hangs: -- --
--   > bilength (BiList [1..] [])
--   * Hangs forever *
--   
bilength :: Bifoldable t => t a b -> Int -- | Does the element occur in the structure? -- --

Examples

-- -- Basic usage: -- --
--   >>> bielem 42 (17, 42)
--   True
--   
-- --
--   >>> bielem 42 (17, 43)
--   False
--   
-- --
--   >>> bielem 42 (Left 42)
--   True
--   
-- --
--   >>> bielem 42 (Right 13)
--   False
--   
-- --
--   >>> bielem 42 (BiList [1..5] [1..100])
--   True
--   
-- --
--   >>> bielem 42 (BiList [1..5] [1..41])
--   False
--   
bielem :: (Bifoldable t, Eq a) => a -> t a a -> Bool -- | The largest element of a non-empty structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> bimaximum (42, 17)
--   42
--   
-- --
--   >>> bimaximum (Right 42)
--   42
--   
-- --
--   >>> bimaximum (BiList [13, 29, 4] [18, 1, 7])
--   29
--   
-- --
--   >>> bimaximum (BiList [13, 29, 4] [])
--   29
--   
-- -- On empty structures, this function throws an exception: -- --
--   >>> bimaximum (BiList [] [])
--   *** Exception: bimaximum: empty structure
--   ...
--   
bimaximum :: (Bifoldable t, Ord a) => t a a -> a -- | The least element of a non-empty structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> biminimum (42, 17)
--   17
--   
-- --
--   >>> biminimum (Right 42)
--   42
--   
-- --
--   >>> biminimum (BiList [13, 29, 4] [18, 1, 7])
--   1
--   
-- --
--   >>> biminimum (BiList [13, 29, 4] [])
--   4
--   
-- -- On empty structures, this function throws an exception: -- --
--   >>> biminimum (BiList [] [])
--   *** Exception: biminimum: empty structure
--   ...
--   
biminimum :: (Bifoldable t, Ord a) => t a a -> a -- | The bisum function computes the sum of the numbers of a -- structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> bisum (42, 17)
--   59
--   
-- --
--   >>> bisum (Right 42)
--   42
--   
-- --
--   >>> bisum (BiList [13, 29, 4] [18, 1, 7])
--   72
--   
-- --
--   >>> bisum (BiList [13, 29, 4] [])
--   46
--   
-- --
--   >>> bisum (BiList [] [])
--   0
--   
bisum :: (Bifoldable t, Num a) => t a a -> a -- | The biproduct function computes the product of the numbers of a -- structure. -- --

Examples

-- -- Basic usage: -- --
--   >>> biproduct (42, 17)
--   714
--   
-- --
--   >>> biproduct (Right 42)
--   42
--   
-- --
--   >>> biproduct (BiList [13, 29, 4] [18, 1, 7])
--   190008
--   
-- --
--   >>> biproduct (BiList [13, 29, 4] [])
--   1508
--   
-- --
--   >>> biproduct (BiList [] [])
--   1
--   
biproduct :: (Bifoldable t, Num a) => t a a -> a -- | Reduces a structure of lists to the concatenation of those lists. -- --

Examples

-- -- Basic usage: -- --
--   >>> biconcat ([1, 2, 3], [4, 5])
--   [1,2,3,4,5]
--   
-- --
--   >>> biconcat (Left [1, 2, 3])
--   [1,2,3]
--   
-- --
--   >>> biconcat (BiList [[1, 2, 3, 4, 5], [6, 7, 8]] [[9]])
--   [1,2,3,4,5,6,7,8,9]
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> biconcatMap (take 3) (fmap digitToInt) ([1..], "89")
--   [1,2,3,8,9]
--   
-- --
--   >>> biconcatMap (take 3) (fmap digitToInt) (Left [1..])
--   [1,2,3]
--   
-- --
--   >>> biconcatMap (take 3) (fmap digitToInt) (Right "89")
--   [8,9]
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> biand (True, False)
--   False
--   
-- --
--   >>> biand (True, True)
--   True
--   
-- --
--   >>> biand (Left True)
--   True
--   
-- -- Empty structures yield True: -- --
--   >>> biand (BiList [] [])
--   True
--   
-- -- A False value finitely far from the left end yields -- False (short circuit): -- --
--   >>> biand (BiList [True, True, False, True] (repeat True))
--   False
--   
-- -- A False value infinitely far from the left end hangs: -- --
--   > biand (BiList (repeat True) [False])
--   * Hangs forever *
--   
-- -- An infinitely True value hangs: -- --
--   > biand (BiList (repeat True) [])
--   * Hangs forever *
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bior (True, False)
--   True
--   
-- --
--   >>> bior (False, False)
--   False
--   
-- --
--   >>> bior (Left True)
--   True
--   
-- -- Empty structures yield False: -- --
--   >>> bior (BiList [] [])
--   False
--   
-- -- A True value finitely far from the left end yields True -- (short circuit): -- --
--   >>> bior (BiList [False, False, True, False] (repeat False))
--   True
--   
-- -- A True value infinitely far from the left end hangs: -- --
--   > bior (BiList (repeat False) [True])
--   * Hangs forever *
--   
-- -- An infinitely False value hangs: -- --
--   > bior (BiList (repeat False) [])
--   * Hangs forever *
--   
bior :: Bifoldable t => t Bool Bool -> Bool -- | Determines whether any element of the structure satisfies its -- appropriate predicate argument. Empty structures yield False. -- --

Examples

-- -- Basic usage: -- --
--   >>> biany even isDigit (27, 't')
--   False
--   
-- --
--   >>> biany even isDigit (27, '8')
--   True
--   
-- --
--   >>> biany even isDigit (26, 't')
--   True
--   
-- --
--   >>> biany even isDigit (Left 27)
--   False
--   
-- --
--   >>> biany even isDigit (Left 26)
--   True
--   
-- --
--   >>> biany even isDigit (BiList [27, 53] ['t', '8'])
--   True
--   
-- -- Empty structures yield False: -- --
--   >>> biany even isDigit (BiList [] [])
--   False
--   
biany :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> Bool -- | Determines whether all elements of the structure satisfy their -- appropriate predicate argument. Empty structures yield True. -- --

Examples

-- -- Basic usage: -- --
--   >>> biall even isDigit (27, 't')
--   False
--   
-- --
--   >>> biall even isDigit (26, '8')
--   True
--   
-- --
--   >>> biall even isDigit (Left 27)
--   False
--   
-- --
--   >>> biall even isDigit (Left 26)
--   True
--   
-- --
--   >>> biall even isDigit (BiList [26, 52] ['3', '8'])
--   True
--   
-- -- Empty structures yield True: -- --
--   >>> biall even isDigit (BiList [] [])
--   True
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bimaximumBy compare (42, 17)
--   42
--   
-- --
--   >>> bimaximumBy compare (Left 17)
--   17
--   
-- --
--   >>> bimaximumBy compare (BiList [42, 17, 23] [-5, 18])
--   42
--   
-- -- On empty structures, this function throws an exception: -- --
--   >>> bimaximumBy compare (BiList [] [])
--   *** Exception: bifoldr1: empty structure
--   ...
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> biminimumBy compare (42, 17)
--   17
--   
-- --
--   >>> biminimumBy compare (Left 17)
--   17
--   
-- --
--   >>> biminimumBy compare (BiList [42, 17, 23] [-5, 18])
--   -5
--   
-- -- On empty structures, this function throws an exception: -- --
--   >>> biminimumBy compare (BiList [] [])
--   *** Exception: bifoldr1: empty structure
--   ...
--   
biminimumBy :: Bifoldable t => (a -> a -> Ordering) -> t a a -> a -- | binotElem is the negation of bielem. -- --

Examples

-- -- Basic usage: -- --
--   >>> binotElem 42 (17, 42)
--   False
--   
-- --
--   >>> binotElem 42 (17, 43)
--   True
--   
-- --
--   >>> binotElem 42 (Left 42)
--   False
--   
-- --
--   >>> binotElem 42 (Right 13)
--   True
--   
-- --
--   >>> binotElem 42 (BiList [1..5] [1..100])
--   False
--   
-- --
--   >>> binotElem 42 (BiList [1..5] [1..41])
--   True
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bifind even (27, 53)
--   Nothing
--   
-- --
--   >>> bifind even (27, 52)
--   Just 52
--   
-- --
--   >>> bifind even (26, 52)
--   Just 26
--   
-- -- Empty structures always yield Nothing: -- --
--   >>> bifind even (BiList [] [])
--   Nothing
--   
bifind :: Bifoldable t => (a -> Bool) -> t a a -> Maybe a instance Data.Bifoldable.Bifoldable Data.Functor.Const.Const instance Data.Bifoldable.Bifoldable Data.Either.Either instance Data.Bifoldable.Bifoldable (GHC.Generics.K1 i) instance Data.Bifoldable.Bifoldable (,) 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) 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 from Data.Functor.Identity and -- Data.Functor.Compose. -- -- 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 :: Type -> Type -> Type) -- | 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_. -- --

Examples

-- -- Basic usage: -- --
--   >>> bitraverse listToMaybe (find odd) (Left [])
--   Nothing
--   
-- --
--   >>> bitraverse listToMaybe (find odd) (Left [1, 2, 3])
--   Just (Left 1)
--   
-- --
--   >>> bitraverse listToMaybe (find odd) (Right [4, 5])
--   Just (Right 5)
--   
-- --
--   >>> bitraverse listToMaybe (find odd) ([1, 2, 3], [4, 5])
--   Just (1,5)
--   
-- --
--   >>> bitraverse listToMaybe (find odd) ([], [4, 5])
--   Nothing
--   
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
--   
-- --

Examples

-- -- Basic usage: -- --
--   >>> bisequence (Just 4, Nothing)
--   Nothing
--   
-- --
--   >>> bisequence (Just 4, Just 5)
--   Just (4,5)
--   
-- --
--   >>> bisequence ([1, 2, 3], [4, 5])
--   [(1,4),(1,5),(2,4),(2,5),(3,4),(3,5)]
--   
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_. -- --

Examples

-- -- Basic usage: -- --
--   >>> bifor (Left []) listToMaybe (find even)
--   Nothing
--   
-- --
--   >>> bifor (Left [1, 2, 3]) listToMaybe (find even)
--   Just (Left 1)
--   
-- --
--   >>> bifor (Right [4, 5]) listToMaybe (find even)
--   Just (Right 4)
--   
-- --
--   >>> bifor ([1, 2, 3], [4, 5]) listToMaybe (find even)
--   Just (1,4)
--   
-- --
--   >>> bifor ([], [4, 5]) listToMaybe (find even)
--   Nothing
--   
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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bimapAccumL (\acc bool -> (acc + 1, show bool)) (\acc string -> (acc * 2, reverse string)) 3 (True, "foo")
--   (8,("True","oof"))
--   
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 bifoldr; 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. -- --

Examples

-- -- Basic usage: -- --
--   >>> bimapAccumR (\acc bool -> (acc + 1, show bool)) (\acc string -> (acc * 2, reverse string)) 3 (True, "foo")
--   (7,("True","oof"))
--   
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 :: 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 :: (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m instance Data.Bitraversable.Bitraversable Data.Functor.Const.Const instance Data.Bitraversable.Bitraversable Data.Either.Either instance Data.Bitraversable.Bitraversable (GHC.Generics.K1 i) 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) -- | 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. It might block, although -- for a very short time; and thus it is interruptible by asynchronous -- exceptions. closeFd :: EventManager -> (Fd -> IO ()) -> Fd -> IO () -- | Warning: since the TimeoutCallback is called from the I/O -- manager, it must not throw an exception or block for a long period of -- time. In particular, be wary of throwTo and killThread: -- if the target thread is making a foreign call, these functions will -- block until the call completes. 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. -- -- Be careful not to exceed maxBound :: Int, which on 32-bit -- machines is only 2147483647 μs, less than 36 minutes. registerTimeout :: TimerManager -> Int -> TimeoutCallback -> IO TimeoutKey -- | Update an active timeout to fire in the given number of microseconds. -- -- Be careful not to exceed maxBound :: Int, which on 32-bit -- machines is only 2147483647 μs, less than 36 minutes. 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 would be difficult to correct while continuing to support -- threadStatus. 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. -- -- WARNING: Exceptions in the new thread will not be rethrown in the -- thread that created it. This means that you might be completely -- unaware of the problem if/when this happens. You may want to use the -- async library instead. 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. 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). It also emits an event to the RTS -- eventlog. 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) -- | List the Haskell threads of the current process. listThreads :: IO [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 -- | Query the current execution status of a thread. 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 a -> 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. -- -- Be careful not to exceed maxBound :: Int, which on 32-bit -- machines is only 2147483647 μs, less than 36 minutes. Consider using -- Control.Concurrent.Thread.Delay.delay from -- unbounded-delays package. threadDelay :: Int -> IO () -- | Switch the value of returned TVar from initial value -- False to True after a given number of microseconds. The -- caveats associated with threadDelay also apply. -- -- Be careful not to exceed maxBound :: Int, which on 32-bit -- machines is only 2147483647 μs, less than 36 minutes. 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. -- -- Using atomically inside an unsafePerformIO or -- unsafeInterleaveIO subverts some of guarantees that STM -- provides. It makes it possible to run a transaction inside of another -- transaction, depending on when the thunk is evaluated. If a nested -- transaction is attempted, an exception is thrown by the runtime. It is -- possible to safely use atomically inside unsafePerformIO -- or unsafeInterleaveIO, but the typechecker does not rule out -- programs that may attempt nested transactions, meaning that the -- programmer must take special care to prevent these. -- -- However, there are functions for creating transactional variables that -- can always be safely called in unsafePerformIO. See: -- newTVarIO, newTChanIO, newBroadcastTChanIO, -- newTQueueIO, newTBQueueIO, and newTMVarIO. -- -- Using unsafePerformIO inside of atomically is also -- dangerous but for different reasons. See unsafeIOToSTM for more -- on this. 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 updated. (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. If the exception is caught via -- catchSTM, only the changes enclosed by the catch are rolled -- back; changes made outside of catchSTM persist. -- -- If the exception is not caught inside of the STM, it is -- re-thrown by atomically, and the entire STM is rolled -- back. -- -- 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 m f catches any exception thrown by -- m using throwSTM, using the function f to -- handle the exception. If an exception is thrown, any changes made by -- m are rolled back, but changes prior to m persist. catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a -- | 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 -- | Provide an IO action with the current value of an MVar. -- The MVar will be empty for the duration that the action is -- running. 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 () -- | Support for catching exceptions raised during top-level computations -- (e.g. Main.main, forkIO, and foreign exports) module GHC.TopHandler -- | runMainIO is wrapped around main (or whatever main is -- called in the program). It catches otherwise uncaught exceptions, and -- also flushes stdout/stderr before exiting. runMainIO :: IO a -> IO a -- | runIO is wrapped around every foreign export and -- foreign import "wrapper" to mop up any uncaught exceptions. -- Thus, the result of running exitWith in a foreign-exported -- function is the same as in the main thread: it terminates the program. runIO :: IO a -> IO a -- | Like runIO, but in the event of an exception that causes an -- exit, we don't shut down the system cleanly, we just exit. This is -- useful in some cases, because the safe exit version will give other -- threads a chance to clean up first, which might shut down the system -- in a different way. For example, try -- -- main = forkIO (runIO (exitWith (ExitFailure 1))) >> threadDelay -- 10000 -- -- This will sometimes exit with "interrupted" and code 0, because the -- main thread is given a chance to shut down when the child thread calls -- safeExit. There is a race to shut down between the main and child -- threads. runIOFastExit :: IO a -> IO a -- | The same as runIO, but for non-IO computations. Used for -- wrapping foreign export and foreign import "wrapper" -- when these are used to export Haskell functions with non-IO types. runNonIO :: a -> IO a topHandler :: SomeException -> IO a topHandlerFastExit :: SomeException -> IO a reportStackOverflow :: IO () reportError :: SomeException -> IO () flushStdHandles :: 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 acquired -- 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 acquired -- 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) -- | 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 would be difficult to correct while continuing to support -- threadStatus. 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. -- -- WARNING: Exceptions in the new thread will not be rethrown in the -- thread that created it. This means that you might be completely -- unaware of the problem if/when this happens. You may want to use the -- async library instead. 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. -- -- Be careful not to exceed maxBound :: Int, which on 32-bit -- machines is only 2147483647 μs, less than 36 minutes. Consider using -- Control.Concurrent.Thread.Delay.delay from -- unbounded-delays package. 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 -- | An exception thrown to a thread by timeout to interrupt a -- timed-out computation. data 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, which on 32-bit -- machines is only 2147483647 μs, less than 36 minutes. Consider using -- Control.Concurrent.Timeout.timeout from -- unbounded-delays package. -- --
--   >>> timeout 1000000 (threadDelay 1000 *> pure "finished on time")
--   Just "finished on time"
--   
-- --
--   >>> timeout 10000 (threadDelay 100000 *> pure "finished on time")
--   Nothing
--   
-- -- 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 (namely throwing the computation the -- Timeout exception). 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.Exception.Type.Exception System.Timeout.Timeout instance GHC.Show.Show System.Timeout.Timeout -- | 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. -- -- "Scrap your boilerplate" --- Generic programming in Haskell. See -- https://wiki.haskell.org/Research_papers/Generics#Scrap_your_boilerplate.21. 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 within 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 -- --
--   instance (Data a, ...) => Data (T a)
--   
-- -- dataCast1 should be defined as gcast1. -- -- The default definition is const Nothing, which -- is appropriate for instances of other forms. 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 -- --
--   instance (Data a, Data b, ...) => Data (T a b)
--   
-- -- dataCast2 should be defined as gcast2. -- -- The default definition is const Nothing, which -- is appropriate for instances of other forms. 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 :: 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 :: 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 :: (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 :: (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Transformation of one immediate subterm with success gmapMo :: (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Representation of datatypes. A package of constructor representations -- with names of type and module. data DataType -- | Constructs an algebraic datatype mkDataType :: String -> [Constr] -> DataType -- | Constructs the Int type mkIntType :: String -> DataType -- | Constructs the Float type mkFloatType :: String -> DataType -- | 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 -- | Constructs a constructor mkConstrTag :: DataType -> String -> Int -> [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 :: (Monad m, Data a) => (forall d. Data d => m d) -> Constr -> m a 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 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 (a GHC.Types.~ b, Data.Data.Data a) => Data.Data.Data (a Data.Type.Equality.:~: b) instance forall i j (a :: i) (b :: j). (Data.Typeable.Internal.Typeable i, Data.Typeable.Internal.Typeable j, Data.Typeable.Internal.Typeable a, Data.Typeable.Internal.Typeable b, a GHC.Types.~~ b) => Data.Data.Data (a Data.Type.Equality.:~~: b) instance Data.Data.Data Data.Semigroup.Internal.All instance (Data.Data.Data (f a), Data.Data.Data a, Data.Typeable.Internal.Typeable f) => Data.Data.Data (Data.Semigroup.Internal.Alt f a) instance Data.Data.Data Data.Semigroup.Internal.Any instance (Data.Data.Data (f a), Data.Data.Data a, Data.Typeable.Internal.Typeable f) => Data.Data.Data (Data.Monoid.Ap f a) instance (Data.Data.Data a, Data.Data.Data b, GHC.Ix.Ix a) => Data.Data.Data (GHC.Arr.Array a b) instance Data.Data.Data GHC.Generics.Associativity instance Data.Data.Data GHC.Types.Bool instance Data.Data.Data GHC.Types.Char instance (GHC.Types.Coercible a b, Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Data.Type.Coercion.Coercion a b) instance forall k a (b :: k). (Data.Typeable.Internal.Typeable k, Data.Data.Data a, Data.Typeable.Internal.Typeable b) => Data.Data.Data (Data.Functor.Const.Const a b) instance Data.Data.Data a => Data.Data.Data (Foreign.C.ConstPtr.ConstPtr a) instance Data.Data.Data GHC.Generics.DecidedStrictness instance Data.Data.Data GHC.Types.Double instance Data.Data.Data a => Data.Data.Data (Data.Ord.Down a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Internal.Dual a) instance (Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Data.Either.Either a b) instance Data.Data.Data a => Data.Data.Data (Data.Monoid.First a) instance Data.Data.Data GHC.Generics.Fixity instance Data.Data.Data GHC.Types.Float instance Data.Data.Data a => Data.Data.Data (GHC.ForeignPtr.ForeignPtr a) instance Data.Data.Data a => Data.Data.Data (Data.Functor.Identity.Identity a) instance Data.Data.Data GHC.Types.Int 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.Int.Int8 instance Data.Data.Data Foreign.Ptr.IntPtr instance Data.Data.Data GHC.Num.Integer.Integer 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 a => Data.Data.Data (Data.Monoid.Last a) instance Data.Data.Data a => Data.Data.Data [a] 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.Data.Data a => Data.Data.Data (GHC.Maybe.Maybe a) instance Data.Data.Data GHC.Num.Natural.Natural instance Data.Data.Data a => Data.Data.Data (GHC.Base.NonEmpty a) instance Data.Data.Data GHC.Types.Ordering instance Data.Data.Data p => Data.Data.Data (GHC.Generics.Par1 p) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Internal.Product a) instance Data.Data.Data t => Data.Data.Data (Data.Proxy.Proxy t) instance Data.Data.Data a => Data.Data.Data (GHC.Ptr.Ptr a) instance (Data.Data.Data a, GHC.Real.Integral a) => Data.Data.Data (GHC.Real.Ratio a) 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.Data.Data a => Data.Data.Data (GHC.Tuple.Prim.Solo a) instance Data.Data.Data GHC.Generics.SourceStrictness instance Data.Data.Data GHC.Generics.SourceUnpackedness instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Internal.Sum a) 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 p => Data.Data.Data (GHC.Generics.U1 p) instance Data.Data.Data () instance Data.Data.Data p => Data.Data.Data (GHC.Generics.V1 p) instance Data.Data.Data Data.Version.Version instance Data.Data.Data GHC.Base.Void instance Data.Data.Data GHC.Types.Word 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 GHC.Word.Word8 instance Data.Data.Data Foreign.Ptr.WordPtr instance (Data.Typeable.Internal.Typeable a, Data.Typeable.Internal.Typeable b, Data.Typeable.Internal.Typeable c, Data.Data.Data (a b c)) => Data.Data.Data (Control.Applicative.WrappedArrow a b c) instance (Data.Typeable.Internal.Typeable m, Data.Typeable.Internal.Typeable a, Data.Data.Data (m a)) => Data.Data.Data (Control.Applicative.WrappedMonad m a) instance Data.Data.Data a => Data.Data.Data (Control.Applicative.ZipList a) instance GHC.Classes.Eq Data.Data.Constr instance GHC.Classes.Eq Data.Data.ConstrRep instance GHC.Classes.Eq Data.Data.DataRep instance GHC.Classes.Eq Data.Data.Fixity instance GHC.Show.Show Data.Data.Constr instance GHC.Show.Show Data.Data.ConstrRep instance GHC.Show.Show Data.Data.DataRep instance GHC.Show.Show Data.Data.DataType instance GHC.Show.Show Data.Data.Fixity -- | 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 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 -- | 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 -- | 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 data TYPE (a :: RuntimeRep) data CONSTRAINT (a :: RuntimeRep) data WordBox (a :: TYPE 'WordRep) MkWordBox :: a -> WordBox (a :: TYPE 'WordRep) data IntBox (a :: TYPE 'IntRep) MkIntBox :: a -> IntBox (a :: TYPE 'IntRep) data FloatBox (a :: TYPE 'FloatRep) MkFloatBox :: a -> FloatBox (a :: TYPE 'FloatRep) data DoubleBox (a :: TYPE 'DoubleRep) MkDoubleBox :: a -> DoubleBox (a :: TYPE 'DoubleRep) -- | Data type Dict provides a simple way to wrap up a (lifted) -- constraint as a type data DictBox a MkDictBox :: DictBox a data Bool False :: Bool True :: Bool -- | The character type Char represents Unicode codespace and its -- elements are code points as in definitions D9 and D10 of the -- Unicode Standard. -- -- Character literals in Haskell are single-quoted: 'Q', -- 'Я' or 'Ω'. To represent a single quote itself use -- '\'', and to represent a backslash use '\\'. The -- full grammar can be found in the section 2.6 of the Haskell 2010 -- Language Report. -- -- To specify a character by its code point one can use decimal, -- hexadecimal or octal notation: '\65', '\x41' and -- '\o101' are all alternative forms of 'A'. The -- largest code point is '\x10ffff'. -- -- There is a special escape syntax for ASCII control characters: -- -- TODO: table -- -- Data.Char provides utilities to work with Char. data Char C# :: Char# -> Char -- | 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 builtin list type, usually written in its non-prefix form -- [a]. -- -- In Haskell, lists are one of the most important data types as they are -- often used analogous to loops in imperative programming languages. -- These lists are singly linked, which makes it unsuited for operations -- that require <math> access. Instead, lists are intended to be -- traversed. -- -- Lists are constructed recursively using the right-associative -- cons-operator (:) :: a -> [a] -> [a], which prepends an -- element to a list, and the empty list []. -- --
--   (1 : 2 : 3 : []) == (1 : (2 : (3 : []))) == [1, 2, 3]
--   
-- -- Internally and in memory, all the above are represented like this, -- with arrows being pointers to locations in memory. -- --
--   ╭───┬───┬──╮   ╭───┬───┬──╮   ╭───┬───┬──╮   ╭────╮
--   │(:)│   │ ─┼──>│(:)│   │ ─┼──>│(:)│   │ ─┼──>│ [] │
--   ╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰────╯
--         v              v              v
--         1              2              3
--   
-- -- As seen above, lists can also be constructed using list literals of -- the form [x_1, x_2, ..., x_n] which are syntactic sugar and, -- unless -XOverloadedLists is enabled, are translated into uses -- of (:) and [] -- -- Similarly, String literals of the form "I 💜 hs" are -- translated into Lists of characters, ['I', ' ', '💜', ' ', 'h', -- 's']. -- --

Examples

-- --
--   >>> ['H', 'a', 's', 'k', 'e', 'l', 'l']
--   "Haskell"
--   
-- --
--   >>> 1 : [4, 1, 5, 9]
--   [1,4,1,5,9]
--   
-- --
--   >>> [] : [] : []
--   [[],[]]
--   
data [] a data Ordering LT :: Ordering EQ :: Ordering GT :: Ordering -- | 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. -- -- In 0.7.0, the fixity was set to infix 4 to match the -- fixity of :~~:. class a ~# b => (a :: k0) ~~ (b :: k1) infix 4 ~~ -- | Lifted, homogeneous equality. By lifted, we mean that it can be bogus -- (deferred type error). By homogeneous, the two types a and -- b must have the same kinds. class a ~# b => (a :: k) ~ (b :: k) infix 4 ~ -- | 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 a ~R# b => Coercible (a :: k) (b :: k) -- | (Kind) This is the kind of type-level symbols. data Symbol -- | 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 -- | boxed; represented by a pointer BoxedRep :: Levity -> RuntimeRep -- | signed, word-sized value IntRep :: RuntimeRep -- | signed, 8-bit value Int8Rep :: RuntimeRep -- | signed, 16-bit value Int16Rep :: RuntimeRep -- | signed, 32-bit value Int32Rep :: RuntimeRep -- | signed, 64-bit value Int64Rep :: RuntimeRep -- | unsigned, word-sized value WordRep :: RuntimeRep -- | unsigned, 8-bit value Word8Rep :: RuntimeRep -- | unsigned, 16-bit value Word16Rep :: RuntimeRep -- | unsigned, 32-bit value Word32Rep :: RuntimeRep -- | unsigned, 64-bit value 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 -- | Whether a boxed type is lifted or unlifted. data Levity Lifted :: Levity Unlifted :: Levity -- | 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 data Multiplicity One :: Multiplicity Many :: Multiplicity -- | SPEC is used by GHC in the SpecConstr pass in order to -- inform the compiler when to be particularly aggressive. In particular, -- it tells GHC to specialize regardless of size or the number of -- specializations. However, not all loops fall into this category. -- -- Libraries can specify this by using SPEC data type to inform -- which loops should be aggressively specialized. For example, instead -- of -- --
--   loop x where loop arg = ...
--   
-- -- write -- --
--   loop SPEC x where loop !_ arg = ...
--   
-- -- There is no semantic difference between SPEC and SPEC2, -- we just need a type with two contructors lest it is optimised away -- before SpecConstr. -- -- This type is reexported from GHC.Exts since GHC 9.0 and -- base-4.15. For compatibility with earlier releases import it -- from GHC.Types in ghc-prim package. data SPEC SPEC :: SPEC SPEC2 :: SPEC pattern TypeLitChar :: () => TypeLitSort pattern TypeLitNat :: () => TypeLitSort pattern TypeLitSymbol :: () => TypeLitSort pattern KindRepTypeLitD :: () => TypeLitSort -> [Char] -> KindRep pattern KindRepTypeLitS :: () => TypeLitSort -> Addr# -> KindRep pattern KindRepTYPE :: () => !RuntimeRep -> KindRep pattern KindRepFun :: () => KindRep -> KindRep -> KindRep pattern KindRepApp :: () => KindRep -> KindRep -> KindRep pattern KindRepVar :: () => !KindBndr -> KindRep pattern KindRepTyConApp :: () => TyCon -> [KindRep] -> KindRep -- | Dynamic pattern TrNameD :: () => [Char] -> TrName -- | Static pattern TrNameS :: () => Addr# -> TrName -- | The kind of the empty unboxed tuple type (# #) type ZeroBitType = TYPE ZeroBitRep -- | The runtime representation of a zero-width tuple, represented by no -- bits at all type ZeroBitRep = 'TupleRep '[] :: [RuntimeRep] -- | The runtime representation of unlifted types. type UnliftedRep = 'BoxedRep 'Unlifted -- | The runtime representation of lifted types. type LiftedRep = 'BoxedRep 'Lifted -- | The kind of boxed, unlifted values, for example Array# or a -- user-defined unlifted data type, using -XUnliftedDataTypes. type UnliftedType = TYPE UnliftedRep -- | The kind of lifted constraints type Constraint = CONSTRAINT LiftedRep -- | 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. type family Any :: k type Void# = (# #) type family MultMul (a :: Multiplicity) (b :: Multiplicity) :: Multiplicity -- | Alias for tagToEnum#. Returns True if its parameter is 1# and -- False if it is 0#. isTrue# :: Int# -> Bool data Word# :: TYPE 'WordRep data Int# :: TYPE 'IntRep -- | An arbitrary machine address assumed to point outside the -- garbage-collected heap. data Addr# :: TYPE 'AddrRep data Array# (a :: TYPE 'BoxedRep l) :: UnliftedType -- | A boxed, unlifted datatype representing a region of raw memory in the -- garbage-collected heap, which is not scanned for pointers during -- garbage collection. -- -- It is created by freezing a MutableByteArray# with -- unsafeFreezeByteArray#. Freezing is essentially a no-op, as -- MutableByteArray# and ByteArray# share the same heap -- structure under the hood. -- -- The immutable and mutable variants are commonly used for scenarios -- requiring high-performance data structures, like Text, -- Primitive Vector, Unboxed Array, and -- ShortByteString. -- -- Another application of fundamental importance is Integer, -- which is backed by ByteArray#. -- -- The representation on the heap of a Byte Array is: -- --
--   +------------+-----------------+-----------------------+
--   |            |                 |                       |
--   |   HEADER   | SIZE (in bytes) |       PAYLOAD         |
--   |            |                 |                       |
--   +------------+-----------------+-----------------------+
--   
-- -- To obtain a pointer to actual payload (e.g., for FFI purposes) use -- byteArrayContents# or mutableByteArrayContents#. -- -- Alternatively, enabling the UnliftedFFITypes extension allows -- to mention ByteArray# and MutableByteArray# in FFI type -- signatures directly. data ByteArray# :: UnliftedType data SmallArray# (a :: TYPE 'BoxedRep l) :: UnliftedType data Char# :: TYPE 'WordRep data Double# :: TYPE 'DoubleRep data Float# :: TYPE 'FloatRep data Int8# :: TYPE 'Int8Rep data Int16# :: TYPE 'Int16Rep data Int32# :: TYPE 'Int32Rep data Int64# :: TYPE 'Int64Rep -- | Primitive bytecode type. data BCO data Weak# (a :: TYPE 'BoxedRep l) :: UnliftedType data MutableArray# a (b :: TYPE 'BoxedRep l) :: UnliftedType -- | A mutable ByteAray#. It can be created in three ways: -- -- -- -- Unpinned arrays can be moved around during garbage collection, so you -- must not store or pass pointers to these values if there is a chance -- for the garbage collector to kick in. That said, even unpinned arrays -- can be passed to unsafe FFI calls, because no garbage collection -- happens during these unsafe calls (see Guaranteed Call Safety -- in the GHC Manual). For safe FFI calls, byte arrays must be not only -- pinned, but also kept alive by means of the keepAlive# function for -- the duration of a call (that's because garbage collection cannot move -- a pinned array, but is free to scrap it altogether). data MutableByteArray# a :: UnliftedType data SmallMutableArray# a (b :: TYPE 'BoxedRep l) :: UnliftedType -- | A shared mutable variable (not the same as a MutVar#!). -- (Note: in a non-concurrent implementation, (MVar# a) -- can be represented by (MutVar# (Maybe a)).) data MVar# a (b :: TYPE 'BoxedRep l) :: UnliftedType -- | A shared I/O port is almost the same as an MVar#. The main -- difference is that IOPort has no deadlock detection or deadlock -- breaking code that forcibly releases the lock. data IOPort# a (b :: TYPE 'BoxedRep l) :: UnliftedType data TVar# a (b :: TYPE 'BoxedRep l) :: UnliftedType -- | A MutVar# behaves like a single-element mutable array. data MutVar# a (b :: TYPE 'BoxedRep l) :: UnliftedType -- | 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 data StablePtr# (a :: TYPE 'BoxedRep l) :: TYPE 'AddrRep data StableName# (a :: TYPE 'BoxedRep l) :: UnliftedType data Compact# :: UnliftedType -- | State# is the primitive, unlifted type of states. It has one -- type parameter, thus State# RealWorld, or -- State# s, where s is a type variable. The only purpose -- of the type parameter is to keep different state threads separate. It -- is represented by nothing at all. data State# a :: ZeroBitType -- | The type constructor Proxy# is used to bear witness to some -- type variable. It's used when you want to pass around proxy values for -- doing things like modelling type applications. A Proxy# is not -- only unboxed, it also has a polymorphic kind, and has no runtime -- representation, being totally free. data Proxy# (a :: k) :: ZeroBitType -- | (In a non-concurrent implementation, this can be a singleton type, -- whose (unique) value is returned by myThreadId#. The other -- operations can be omitted.) data ThreadId# :: UnliftedType data Word8# :: TYPE 'Word8Rep data Word16# :: TYPE 'Word16Rep data Word32# :: TYPE 'Word32Rep data Word64# :: TYPE 'Word64Rep -- | Haskell representation of a StgStack* that was created -- (cloned) with a function in GHC.Stack.CloneStack. Please check -- the documentation in that module for more detailed explanations. data StackSnapshot# :: UnliftedType -- | See GHC.Prim#continuations. data PromptTag# a :: UnliftedType -- | The builtin function type, written in infix form as a % m -> -- b. Values of this type are functions taking inputs of type -- a and producing outputs of type b. The multiplicity -- of the input is m. -- -- Note that FUN m a b permits representation -- polymorphism in both a and b, so that types like -- Int# -> Int# can still be well-kinded. data FUN data TYPE (a :: RuntimeRep) data CONSTRAINT (a :: RuntimeRep) -- | Warning: this is only available on LLVM. data Int8X16# :: TYPE 'VecRep 'Vec16 'Int8ElemRep -- | Warning: this is only available on LLVM. data Int16X8# :: TYPE 'VecRep 'Vec8 'Int16ElemRep -- | Warning: this is only available on LLVM. data Int32X4# :: TYPE 'VecRep 'Vec4 'Int32ElemRep -- | Warning: this is only available on LLVM. data Int64X2# :: TYPE 'VecRep 'Vec2 'Int64ElemRep -- | Warning: this is only available on LLVM. data Int8X32# :: TYPE 'VecRep 'Vec32 'Int8ElemRep -- | Warning: this is only available on LLVM. data Int16X16# :: TYPE 'VecRep 'Vec16 'Int16ElemRep -- | Warning: this is only available on LLVM. data Int32X8# :: TYPE 'VecRep 'Vec8 'Int32ElemRep -- | Warning: this is only available on LLVM. data Int64X4# :: TYPE 'VecRep 'Vec4 'Int64ElemRep -- | Warning: this is only available on LLVM. data Int8X64# :: TYPE 'VecRep 'Vec64 'Int8ElemRep -- | Warning: this is only available on LLVM. data Int16X32# :: TYPE 'VecRep 'Vec32 'Int16ElemRep -- | Warning: this is only available on LLVM. data Int32X16# :: TYPE 'VecRep 'Vec16 'Int32ElemRep -- | Warning: this is only available on LLVM. data Int64X8# :: TYPE 'VecRep 'Vec8 'Int64ElemRep -- | Warning: this is only available on LLVM. data Word8X16# :: TYPE 'VecRep 'Vec16 'Word8ElemRep -- | Warning: this is only available on LLVM. data Word16X8# :: TYPE 'VecRep 'Vec8 'Word16ElemRep -- | Warning: this is only available on LLVM. data Word32X4# :: TYPE 'VecRep 'Vec4 'Word32ElemRep -- | Warning: this is only available on LLVM. data Word64X2# :: TYPE 'VecRep 'Vec2 'Word64ElemRep -- | Warning: this is only available on LLVM. data Word8X32# :: TYPE 'VecRep 'Vec32 'Word8ElemRep -- | Warning: this is only available on LLVM. data Word16X16# :: TYPE 'VecRep 'Vec16 'Word16ElemRep -- | Warning: this is only available on LLVM. data Word32X8# :: TYPE 'VecRep 'Vec8 'Word32ElemRep -- | Warning: this is only available on LLVM. data Word64X4# :: TYPE 'VecRep 'Vec4 'Word64ElemRep -- | Warning: this is only available on LLVM. data Word8X64# :: TYPE 'VecRep 'Vec64 'Word8ElemRep -- | Warning: this is only available on LLVM. data Word16X32# :: TYPE 'VecRep 'Vec32 'Word16ElemRep -- | Warning: this is only available on LLVM. data Word32X16# :: TYPE 'VecRep 'Vec16 'Word32ElemRep -- | Warning: this is only available on LLVM. data Word64X8# :: TYPE 'VecRep 'Vec8 'Word64ElemRep -- | Warning: this is only available on LLVM. data FloatX4# :: TYPE 'VecRep 'Vec4 'FloatElemRep -- | Warning: this is only available on LLVM. data DoubleX2# :: TYPE 'VecRep 'Vec2 'DoubleElemRep -- | Warning: this is only available on LLVM. data FloatX8# :: TYPE 'VecRep 'Vec8 'FloatElemRep -- | Warning: this is only available on LLVM. data DoubleX4# :: TYPE 'VecRep 'Vec4 'DoubleElemRep -- | Warning: this is only available on LLVM. data FloatX16# :: TYPE 'VecRep 'Vec16 'FloatElemRep -- | Warning: this is only available on LLVM. data DoubleX8# :: TYPE 'VecRep 'Vec8 'DoubleElemRep prefetchValue0# :: a -> State# d -> State# d prefetchAddr0# :: Addr# -> Int# -> State# d -> State# d prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d prefetchValue1# :: a -> State# d -> State# d prefetchAddr1# :: Addr# -> Int# -> State# d -> State# d prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d prefetchValue2# :: a -> State# d -> State# d prefetchAddr2# :: Addr# -> Int# -> State# d -> State# d prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d prefetchValue3# :: a -> State# d -> State# d prefetchAddr3# :: Addr# -> Int# -> State# d -> State# d prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d -- | Write vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #) -- | Read a vector from specified index of mutable array of scalars; offset -- is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #) -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8# -- | Read a vector from specified index of immutable array of scalars; -- offset is in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16# -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d -- | Write vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d -- | Write a vector to specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #) -- | Read a vector from specified index of mutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #) -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8# -- | Read a vector from specified index of immutable array. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateDoubleX8# :: DoubleX8# -> DoubleX8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateFloatX16# :: FloatX16# -> FloatX16# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateDoubleX4# :: DoubleX4# -> DoubleX4# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateFloatX8# :: FloatX8# -> FloatX8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateDoubleX2# :: DoubleX2# -> DoubleX2# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateFloatX4# :: FloatX4# -> FloatX4# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt64X8# :: Int64X8# -> Int64X8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt32X16# :: Int32X16# -> Int32X16# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt16X32# :: Int16X32# -> Int16X32# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt8X64# :: Int8X64# -> Int8X64# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt64X4# :: Int64X4# -> Int64X4# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt32X8# :: Int32X8# -> Int32X8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt16X16# :: Int16X16# -> Int16X16# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt8X32# :: Int8X32# -> Int8X32# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt64X2# :: Int64X2# -> Int64X2# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt32X4# :: Int32X4# -> Int32X4# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt16X8# :: Int16X8# -> Int16X8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt8X16# :: Int8X16# -> Int8X16# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# -- | Satisfies (quot# x y) times# y plus# -- (rem# x y) == x. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- | Divide two vectors element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -- | Divide two vectors element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -- | Divide two vectors element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -- | Divide two vectors element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -- | Divide two vectors element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -- | Divide two vectors element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord16X32# :: Word16X32# -> Word16# -> Int# -> Word16X32# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord8X64# :: Word8X64# -> Word8# -> Int# -> Word8X64# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord16X16# :: Word16X16# -> Word16# -> Int# -> Word16X16# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord8X32# :: Word8X32# -> Word8# -> Int# -> Word8X32# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord16X8# :: Word16X8# -> Word16# -> Int# -> Word16X8# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertWord8X16# :: Word8X16# -> Word8# -> Int# -> Word8X16# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8# -- | Insert a scalar at the given position in a vector. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. insertInt8X16# :: Int8X16# -> Int8# -> Int# -> Int8X16# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackDoubleX8# :: DoubleX8# -> (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackFloatX16# :: FloatX16# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackDoubleX4# :: DoubleX4# -> (# Double#, Double#, Double#, Double# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackFloatX8# :: FloatX8# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackDoubleX2# :: DoubleX2# -> (# Double#, Double# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackFloatX4# :: FloatX4# -> (# Float#, Float#, Float#, Float# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord64X8# :: Word64X8# -> (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord32X16# :: Word32X16# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord16X32# :: Word16X32# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord8X64# :: Word8X64# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord64X4# :: Word64X4# -> (# Word64#, Word64#, Word64#, Word64# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord32X8# :: Word32X8# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord16X16# :: Word16X16# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord8X32# :: Word8X32# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord64X2# :: Word64X2# -> (# Word64#, Word64# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord32X4# :: Word32X4# -> (# Word32#, Word32#, Word32#, Word32# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord16X8# :: Word16X8# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord8X16# :: Word8X16# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt64X8# :: Int64X8# -> (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt32X16# :: Int32X16# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt16X32# :: Int16X32# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt8X64# :: Int8X64# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt64X4# :: Int64X4# -> (# Int64#, Int64#, Int64#, Int64# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt32X8# :: Int32X8# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt16X16# :: Int16X16# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt8X32# :: Int8X32# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt64X2# :: Int64X2# -> (# Int64#, Int64# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt32X4# :: Int32X4# -> (# Int32#, Int32#, Int32#, Int32# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt16X8# :: Int16X8# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt8X16# :: Int8X16# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packDoubleX8# :: (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -> DoubleX8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packFloatX16# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packDoubleX4# :: (# Double#, Double#, Double#, Double# #) -> DoubleX4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packFloatX8# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packDoubleX2# :: (# Double#, Double# #) -> DoubleX2# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packFloatX4# :: (# Float#, Float#, Float#, Float# #) -> FloatX4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord64X8# :: (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -> Word64X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord32X16# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord16X32# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord8X64# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X64# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord64X4# :: (# Word64#, Word64#, Word64#, Word64# #) -> Word64X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord32X8# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord16X16# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord8X32# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord64X2# :: (# Word64#, Word64# #) -> Word64X2# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord32X4# :: (# Word32#, Word32#, Word32#, Word32# #) -> Word32X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord16X8# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord8X16# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt64X8# :: (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -> Int64X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt32X16# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt16X32# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt8X64# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X64# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt64X4# :: (# Int64#, Int64#, Int64#, Int64# #) -> Int64X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt32X8# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt16X16# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt8X32# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt64X2# :: (# Int64#, Int64# #) -> Int64X2# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt32X4# :: (# Int32#, Int32#, Int32#, Int32# #) -> Int32X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt16X8# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt8X16# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastDoubleX8# :: Double# -> DoubleX8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastFloatX16# :: Float# -> FloatX16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastDoubleX4# :: Double# -> DoubleX4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastFloatX8# :: Float# -> FloatX8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastDoubleX2# :: Double# -> DoubleX2# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastFloatX4# :: Float# -> FloatX4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord64X8# :: Word64# -> Word64X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord32X16# :: Word32# -> Word32X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord16X32# :: Word16# -> Word16X32# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord8X64# :: Word8# -> Word8X64# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord64X4# :: Word64# -> Word64X4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord32X8# :: Word32# -> Word32X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord16X16# :: Word16# -> Word16X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord8X32# :: Word8# -> Word8X32# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord64X2# :: Word64# -> Word64X2# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord32X4# :: Word32# -> Word32X4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord16X8# :: Word16# -> Word16X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord8X16# :: Word8# -> Word8X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt64X8# :: Int64# -> Int64X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt32X16# :: Int32# -> Int32X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt16X32# :: Int16# -> Int16X32# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt8X64# :: Int8# -> Int8X64# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt64X4# :: Int64# -> Int64X4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt32X8# :: Int32# -> Int32X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt16X16# :: Int16# -> Int16X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt8X32# :: Int8# -> Int8X32# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt64X2# :: Int64# -> Int64X2# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt32X4# :: Int32# -> Int32X4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt16X8# :: Int16# -> Int16X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt8X16# :: Int8# -> Int8X16# -- | Sets the allocation counter for the current thread to the given value. setThreadAllocationCounter# :: Int64# -> State# RealWorld -> State# RealWorld -- | Emits a marker event via the RTS tracing framework. The contents of -- the event is the zero-terminated byte string passed as the first -- argument. The event will be emitted either to the .eventlog -- file, or to stderr, depending on the runtime RTS flags. traceMarker# :: Addr# -> State# d -> State# d -- | Emits an event via the RTS tracing framework. The contents of the -- event is the binary object passed as the first argument with the given -- length passed as the second argument. The event will be emitted to the -- .eventlog file. traceBinaryEvent# :: Addr# -> Int# -> State# d -> State# d -- | Emits an event via the RTS tracing framework. The contents of the -- event is the zero-terminated byte string passed as the first argument. -- The event will be emitted either to the .eventlog file, or to -- stderr, depending on the runtime RTS flags. traceEvent# :: Addr# -> State# d -> State# d -- | Returns the InfoProvEnt for the info table of the given -- object (value is NULL if the table does not exist or there is -- no information about the closure). whereFrom# :: a -> State# d -> (# State# d, Addr# #) -- | Run the supplied IO action with an empty CCS. For example, this is -- used by the interpreter to run an interpreted computation without the -- call stack showing that it was invoked from GHC. clearCCS# :: (State# d -> (# State# d, a #)) -> State# d -> (# State# d, a #) -- | Returns the current CostCentreStack (value is NULL -- if not profiling). Takes a dummy argument which can be used to avoid -- the call to getCurrentCCS# being floated out by the simplifier, -- which would result in an uninformative stack (CAF). getCurrentCCS# :: a -> State# d -> (# State# d, Addr# #) getCCSOf# :: a -> State# d -> (# State# d, Addr# #) getApStackVal# :: a -> Int# -> (# Int#, b #) -- | closureSize# closure returns the size of the given -- closure in machine words. closureSize# :: a -> Int# -- | unpackClosure# closure copies the closure and pointers -- in the payload of the given closure into two new arrays, and returns a -- pointer to the first word of the closure's info table, a non-pointer -- array for the raw bytes of the closure, and a pointer array for the -- pointers in the payload. unpackClosure# :: a -> (# Addr#, ByteArray#, Array# b #) -- | newBCO# instrs lits ptrs arity bitmap creates a new -- bytecode object. The resulting object encodes a function of the given -- arity with the instructions encoded in instrs, and a static -- reference table usage bitmap given by bitmap. newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) -- | Wrap a BCO in a AP_UPD thunk which will be updated with the -- value of the BCO when evaluated. mkApUpd0# :: BCO -> (# a #) -- | Retrieve the address of any Haskell value. This is essentially an -- unsafeCoerce#, but if implemented as such the core lint pass -- complains and fails to compile. As a primop, it is opaque to core/stg, -- and only appears in cmm (where the copy propagation pass will get rid -- of it). Note that "a" must be a value, not a thunk! It's too late for -- strictness analysis to enforce this, so you're on your own to -- guarantee this. Also note that Addr# is not a GC pointer - up -- to you to guarantee that it does not become a dangling pointer -- immediately after you get it. anyToAddr# :: a -> State# RealWorld -> (# State# RealWorld, Addr# #) -- | Convert an Addr# to a followable Any type. addrToAny# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Addr# -> (# a #) tagToEnum# :: Int# -> a -- | Evaluates the argument and returns the tag of the result. Tags are -- Zero-indexed; the first constructor has tag zero. dataToTag# :: a -> Int# -- | keepAlive# x s k keeps the value x alive -- during the execution of the computation k. -- -- Note that the result type here isn't quite as unrestricted as the -- polymorphic type might suggest; see the section "RuntimeRep -- polymorphism in continuation-style primops" for details. keepAlive# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) d (b :: TYPE r). a -> State# d -> (State# d -> b) -> b -- | Returns the number of sparks in the local spark pool. numSparks# :: State# d -> (# State# d, Int# #) getSpark# :: State# d -> (# State# d, Int#, a #) seq# :: a -> State# d -> (# State# d, a #) spark# :: a -> State# d -> (# State# d, a #) par# :: a -> Int# -- | Returns 1# if the given pointers are equal and 0# -- otherwise. -- -- Warning: this can fail with an unchecked exception. reallyUnsafePtrEquality# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> Int# -- | Return the total capacity (in bytes) of all the compact blocks in the -- CNF. compactSize# :: Compact# -> State# RealWorld -> (# State# RealWorld, Word# #) -- | Like compactAdd#, but retains sharing and cycles during -- compaction. compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) -- | Recursively add a closure and its transitive closure to a -- Compact# (a CNF), evaluating any unevaluated components at the -- same time. Note: compactAdd# is not thread-safe, so only one -- thread may call compactAdd# with a particular Compact# -- at any given time. The primop does not enforce any mutual exclusion; -- the caller is expected to arrange this. compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) -- | Given the pointer to the first block of a CNF and the address of the -- root object in the old address space, fix up the internal pointers -- inside the CNF to account for a different position in memory than when -- it was serialized. This method must be called exactly once after -- importing a serialized CNF. It returns the new CNF and the new -- adjusted root address. compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Compact#, Addr# #) -- | Attempt to allocate a compact block with the capacity (in bytes) given -- by the first argument. The Addr# is a pointer to previous -- compact block of the CNF or nullAddr# to create a new CNF with -- a single compact block. -- -- The resulting block is not known to the GC until -- compactFixupPointers# is called on it, and care must be taken -- so that the address does not escape or memory will be leaked. compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #) -- | Given a CNF and the address of one its compact blocks, returns the -- next compact block and its utilized size, or nullAddr# if the -- argument was the last compact block in the CNF. compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) -- | Returns the address and the utilized size (in bytes) of the first -- compact block of a CNF. compactGetFirstBlock# :: Compact# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) -- | Returns 1# if the object is in any CNF at all, 0# otherwise. compactContainsAny# :: a -> State# RealWorld -> (# State# RealWorld, Int# #) -- | Returns 1# if the object is contained in the CNF, 0# otherwise. compactContains# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, Int# #) -- | Set the new allocation size of the CNF. This value (in bytes) -- determines the capacity of each compact block in the CNF. It does not -- retroactively affect existing compact blocks in the CNF. compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld -- | Create a new CNF with a single compact block. The argument is the -- capacity of the compact block (in bytes, not words). The capacity is -- rounded up to a multiple of the allocator block size and is capped to -- one mega block. compactNew# :: Word# -> State# RealWorld -> (# State# RealWorld, Compact# #) stableNameToInt# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StableName# a -> Int# makeStableName# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StableName# a #) eqStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> StablePtr# a -> Int# deRefStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #) makeStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #) touch# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> State# d -- | Finalize a weak pointer. The return value is an unboxed tuple -- containing the new state of the world and an "unboxed Maybe", -- represented by an Int# and a (possibly invalid) finalization -- action. An Int# of 1 indicates that the finalizer is -- valid. The return value b from the finalizer should be -- ignored. finalizeWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) deRefWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #) -- | addCFinalizerToWeak# fptr ptr flag eptr w attaches a C -- function pointer fptr to a weak pointer w as a -- finalizer. If flag is zero, fptr will be called with -- one argument, ptr. Otherwise, it will be called with two -- arguments, eptr and ptr. addCFinalizerToWeak# -- returns 1 on success, or 0 if w is already dead. addCFinalizerToWeak# :: forall {k :: Levity} (b :: TYPE ('BoxedRep k)). Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #) mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) -- | mkWeak# k v finalizer s creates a weak reference to -- value k, with an associated reference to some value -- v. If k is still alive then v can be -- retrieved using deRefWeak#. Note that the type of k -- must be represented by a pointer (i.e. of kind TYPE -- 'LiftedRep or TYPE 'UnliftedRep@). mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) -- | Returns an array of the threads started by the program. Note that this -- threads which have finished execution may or may not be present in -- this list, depending upon whether they have been collected by the -- garbage collector. listThreads# :: State# RealWorld -> (# State# RealWorld, Array# ThreadId# #) -- | Get the status of the given thread. Result is (ThreadStatus, -- Capability, Locked) where ThreadStatus is one of the -- status constants defined in rts/Constants.h, -- Capability is the number of the capability which currently -- owns the thread, and Locked is a boolean indicating whether -- the thread is bound to that capability. threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #) -- | Get the label of the given thread. Morally of type ThreadId# -> -- IO (Maybe ByteArray#), with a 1# tag denoting -- Just. threadLabel# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, ByteArray# #) noDuplicate# :: State# d -> State# d isCurrentThreadBound# :: State# RealWorld -> (# State# RealWorld, Int# #) -- | Set the label of the given thread. The ByteArray# should -- contain a UTF-8-encoded string. labelThread# :: ThreadId# -> ByteArray# -> State# RealWorld -> State# RealWorld myThreadId# :: State# RealWorld -> (# State# RealWorld, ThreadId# #) yield# :: State# RealWorld -> State# RealWorld killThread# :: ThreadId# -> a -> State# RealWorld -> State# RealWorld forkOn# :: forall {q :: RuntimeRep} (a :: TYPE q). Int# -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) fork# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) -- | Block until output is possible on specified file descriptor. waitWrite# :: Int# -> State# d -> State# d -- | Block until input is available on specified file descriptor. waitRead# :: Int# -> State# d -> State# d -- | Sleep specified number of microseconds. delay# :: Int# -> State# d -> State# d -- | If IOPort# is full, immediately return with integer 0, throwing -- an IOPortException. Otherwise, store value arg as 'IOPort#''s -- new contents, and return with integer 1. writeIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> a -> State# d -> (# State# d, Int# #) -- | If IOPort# is empty, block until it becomes full. Then remove -- and return its contents, and set it empty. Throws an -- IOPortException if another thread is already waiting to read -- this IOPort#. readIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> State# d -> (# State# d, a #) -- | Create new IOPort#; initially empty. newIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, IOPort# d a #) -- | Return 1 if MVar# is empty; 0 otherwise. isEmptyMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int# #) -- | If MVar# is empty, immediately return with integer 0 and value -- undefined. Otherwise, return with integer 1 and contents of -- MVar#. tryReadMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) -- | If MVar# is empty, block until it becomes full. Then read its -- contents without modifying the MVar, without possibility of -- intervention from other threads. readMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) -- | If MVar# is full, immediately return with integer 0. Otherwise, -- store value arg as 'MVar#''s new contents, and return with integer 1. tryPutMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> (# State# d, Int# #) -- | If MVar# is full, block until it becomes empty. Then store -- value arg as its new contents. putMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> State# d -- | If MVar# is empty, immediately return with integer 0 and value -- undefined. Otherwise, return with integer 1 and contents of -- MVar#, and set MVar# empty. tryTakeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) -- | If MVar# is empty, block until it becomes full. Then remove and -- return its contents, and set it empty. takeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) -- | Create new MVar#; initially empty. newMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, MVar# d a #) -- | Write contents of TVar#. writeTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> a -> State# d -> State# d -- | Read contents of TVar# outside an STM transaction. Does not -- force evaluation of the result. readTVarIO# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) -- | Read contents of TVar# inside an STM transaction, i.e. within a -- call to atomically#. Does not force evaluation of the result. readTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) -- | Create a new TVar# holding a specified initial value. newTVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, TVar# d a #) catchSTM# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) catchRetry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) retry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). State# RealWorld -> (# State# RealWorld, a #) atomically# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) -- | See GHC.Prim#continuations. control0# :: forall {r :: RuntimeRep} a (b :: TYPE r). PromptTag# a -> (((State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, b #) -- | See GHC.Prim#continuations. prompt# :: PromptTag# a -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) -- | See GHC.Prim#continuations. newPromptTag# :: State# RealWorld -> (# State# RealWorld, PromptTag# a #) getMaskingState# :: State# RealWorld -> (# State# RealWorld, Int# #) -- | unmaskAsyncUninterruptible# k s evaluates k -- s such that asynchronous exceptions are unmasked. -- -- Note that the result type here isn't quite as unrestricted as the -- polymorphic type might suggest; see the section "RuntimeRep -- polymorphism in continuation-style primops" for details. unmaskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) -- | maskUninterruptible# k s evaluates k s such -- that asynchronous exceptions are deferred until after evaluation has -- finished. -- -- Note that the result type here isn't quite as unrestricted as the -- polymorphic type might suggest; see the section "RuntimeRep -- polymorphism in continuation-style primops" for details. maskUninterruptible# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) -- | maskAsyncExceptions# k s evaluates k s such -- that asynchronous exceptions are deferred until after evaluation has -- finished. -- -- Note that the result type here isn't quite as unrestricted as the -- polymorphic type might suggest; see the section "RuntimeRep -- polymorphism in continuation-style primops" for details. maskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) raiseIO# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> State# RealWorld -> (# State# RealWorld, b #) -- | Warning: this can fail with an unchecked exception. raiseDivZero# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b -- | Warning: this can fail with an unchecked exception. raiseOverflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b -- | Warning: this can fail with an unchecked exception. raiseUnderflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b -- | Warning: this can fail with an unchecked exception. raise# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> b -- | catch# k handler s evaluates k s, invoking -- handler on any exceptions thrown. -- -- Note that the result type here isn't quite as unrestricted as the -- polymorphic type might suggest; see the section "RuntimeRep -- polymorphism in continuation-style primops" for details. catch# :: forall {q :: RuntimeRep} {k :: Levity} (a :: TYPE q) (b :: TYPE ('BoxedRep k)). (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) -- | Compare-and-swap: perform a pointer equality test between the first -- value passed to this function and the value stored inside the -- MutVar#. If the pointers are equal, replace the stored value -- with the second value passed to this function, otherwise do nothing. -- Returns the final value stored inside the MutVar#. The -- Int# indicates whether a swap took place, with 1# -- meaning that we didn't swap, and 0# that we did. Implies a -- full memory barrier. Because the comparison is done on the level of -- pointers, all of the difficulties of using -- reallyUnsafePtrEquality# correctly apply to casMutVar# -- as well. casMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #) -- | Modify the contents of a MutVar#, returning the previous -- contents and the result of applying the given function to the previous -- contents. -- -- Warning: this can fail with an unchecked exception. atomicModifyMutVar_# :: MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #) -- | Modify the contents of a MutVar#, returning the previous -- contents x :: a and the result of applying the given function -- to the previous contents f x :: c. -- -- The data type c (not a newtype!) must be a -- record whose first field is of lifted type a :: Type and is -- not unpacked. For example, product types c ~ Solo a or c -- ~ (a, b) work well. If the record type is both monomorphic and -- strict in its first field, it's recommended to mark the latter {-# -- NOUNPACK #-} explicitly. -- -- Under the hood atomicModifyMutVar2# atomically replaces a -- pointer to an old x :: a with a pointer to a selector thunk -- fst r, where fst is a selector for the first field -- of the record and r is a function application thunk r = f -- x. -- -- atomicModifyIORef2Native from atomic-modify-general -- package makes an effort to reflect restrictions on c -- faithfully, providing a well-typed high-level wrapper. -- -- Warning: this can fail with an unchecked exception. atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #) -- | Atomically exchange the value of a MutVar#. atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #) -- | Write contents of MutVar#. writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d -- | Read contents of MutVar#. Result is not yet evaluated. readMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #) -- | Create MutVar# with specified initial value in specified state -- thread. newMutVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #) -- | Given an address, write a machine word. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicWriteWordAddr# :: Addr# -> Word# -> State# d -> State# d -- | Given an address, read a machine word. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicReadWordAddr# :: Addr# -> State# d -> (# State# d, Word# #) -- | Given an address, and a value to XOR, atomically XOR the value into -- the element. Returns the value of the element before the operation. -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchXorWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) -- | Given an address, and a value to OR, atomically OR the value into the -- element. Returns the value of the element before the operation. -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchOrWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) -- | Given an address, and a value to NAND, atomically NAND the value into -- the element. Returns the value of the element before the operation. -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchNandWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) -- | Given an address, and a value to AND, atomically AND the value into -- the element. Returns the value of the element before the operation. -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchAndWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) -- | Given an address, and a value to subtract, atomically subtract the -- value from the element. Returns the value of the element before the -- operation. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchSubWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) -- | Given an address, and a value to add, atomically add the value to the -- element. Returns the value of the element before the operation. -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchAddWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) -- | Compare and swap on a 64 bit-sized and aligned memory location. -- -- Use as: s -> atomicCasWordAddr64# location expected desired s -- -- This version always returns the old value read. This follows the -- normal protocol for CAS operations (and matches the underlying -- instruction on most architectures). -- -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicCasWord64Addr# :: Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #) -- | Compare and swap on a 32 bit-sized and aligned memory location. -- -- Use as: s -> atomicCasWordAddr32# location expected desired s -- -- This version always returns the old value read. This follows the -- normal protocol for CAS operations (and matches the underlying -- instruction on most architectures). -- -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicCasWord32Addr# :: Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #) -- | Compare and swap on a 16 bit-sized and aligned memory location. -- -- Use as: s -> atomicCasWordAddr16# location expected desired s -- -- This version always returns the old value read. This follows the -- normal protocol for CAS operations (and matches the underlying -- instruction on most architectures). -- -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicCasWord16Addr# :: Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #) -- | Compare and swap on a 8 bit-sized and aligned memory location. -- -- Use as: s -> atomicCasWordAddr8# location expected desired s -- -- This version always returns the old value read. This follows the -- normal protocol for CAS operations (and matches the underlying -- instruction on most architectures). -- -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicCasWord8Addr# :: Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #) -- | Compare and swap on a word-sized and aligned memory location. -- -- Use as: s -> atomicCasWordAddr# location expected desired s -- -- This version always returns the old value read. This follows the -- normal protocol for CAS operations (and matches the underlying -- instruction on most architectures). -- -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #) -- | Compare and swap on a word-sized memory location. -- -- Use as: s -> atomicCasAddrAddr# location expected desired s -- -- This version always returns the old value read. This follows the -- normal protocol for CAS operations (and matches the underlying -- instruction on most architectures). -- -- Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #) -- | The atomic exchange operation. Atomically exchanges the value at the -- address with the given value. Returns the old value. Implies a read -- barrier. -- -- Warning: this can fail with an unchecked exception. atomicExchangeWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) -- | The atomic exchange operation. Atomically exchanges the value at the -- first address with the Addr# given as second argument. Implies a read -- barrier. -- -- Warning: this can fail with an unchecked exception. atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# d -> (# State# d, Addr# #) -- | Write a 64-bit unsigned integer; offset in 8-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d -- | Write a 64-bit signed integer; offset in 8-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d -- | Write a 32-bit unsigned integer; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d -- | Write a 32-bit signed integer; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d -- | Write a 16-bit unsigned integer; offset in 2-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d -- | Write a 16-bit signed integer; offset in 2-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d -- | Write an 8-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d -- | Write an 8-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d -- | Write a StablePtr# value; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d -- | Write a double-precision floating-point value; offset in 8-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d -- | Write a single-precision floating-point value; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d -- | Write a machine address; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d -- | Write a word-sized unsigned integer; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d -- | Write a word-sized integer; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d -- | Write a 32-bit character; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d -- | Write an 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d -- | Read a 64-bit unsigned integer; offset in 8-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) -- | Read a 64-bit signed integer; offset in 8-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) -- | Read a 32-bit unsigned integer; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) -- | Read a 32-bit signed integer; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) -- | Read a 16-bit unsigned integer; offset in 2-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) -- | Read a 16-bit signed integer; offset in 2-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) -- | Read an 8-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #) -- | Read an 8-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #) -- | Read a StablePtr# value; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) -- | Read a double-precision floating-point value; offset in 8-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) -- | Read a single-precision floating-point value; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) -- | Read a machine address; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) -- | Read a word-sized unsigned integer; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) -- | Read a word-sized integer; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) -- | Read a 32-bit character; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) -- | Read an 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) -- | Read a 64-bit unsigned integer; offset in 8-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexWord64OffAddr# :: Addr# -> Int# -> Word64# -- | Read a 64-bit signed integer; offset in 8-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexInt64OffAddr# :: Addr# -> Int# -> Int64# -- | Read a 32-bit unsigned integer; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexWord32OffAddr# :: Addr# -> Int# -> Word32# -- | Read a 32-bit signed integer; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexInt32OffAddr# :: Addr# -> Int# -> Int32# -- | Read a 16-bit unsigned integer; offset in 2-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexWord16OffAddr# :: Addr# -> Int# -> Word16# -- | Read a 16-bit signed integer; offset in 2-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexInt16OffAddr# :: Addr# -> Int# -> Int16# -- | Read an 8-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8OffAddr# :: Addr# -> Int# -> Word8# -- | Read an 8-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexInt8OffAddr# :: Addr# -> Int# -> Int8# -- | Read a StablePtr# value; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -- | Read a double-precision floating-point value; offset in 8-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexDoubleOffAddr# :: Addr# -> Int# -> Double# -- | Read a single-precision floating-point value; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexFloatOffAddr# :: Addr# -> Int# -> Float# -- | Read a machine address; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexAddrOffAddr# :: Addr# -> Int# -> Addr# -- | Read a word-sized unsigned integer; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexWordOffAddr# :: Addr# -> Int# -> Word# -- | Read a word-sized integer; offset in machine words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexIntOffAddr# :: Addr# -> Int# -> Int# -- | Read a 32-bit character; offset in 4-byte words. -- -- On some platforms, the access may fail for an insufficiently aligned -- Addr#. -- -- Warning: this can fail with an unchecked exception. indexWideCharOffAddr# :: Addr# -> Int# -> Char# -- | Read an 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexCharOffAddr# :: Addr# -> Int# -> Char# leAddr# :: Addr# -> Addr# -> Int# ltAddr# :: Addr# -> Addr# -> Int# neAddr# :: Addr# -> Addr# -> Int# eqAddr# :: Addr# -> Addr# -> Int# geAddr# :: Addr# -> Addr# -> Int# gtAddr# :: Addr# -> Addr# -> Int# -- | Coerce directly from int to address. int2Addr# :: Int# -> Addr# -- | Coerce directly from address to int. addr2Int# :: Addr# -> Int# -- | Return the remainder when the Addr# arg, treated like an -- Int#, is divided by the Int# arg. remAddr# :: Addr# -> Int# -> Int# -- | Result is meaningless if two Addr#s are so far apart that their -- difference doesn't fit in an Int#. minusAddr# :: Addr# -> Addr# -> Int# plusAddr# :: Addr# -> Int# -> Addr# -- | Given an array, and offset in machine words, and a value to XOR, -- atomically XOR the value into the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) -- | Given an array, and offset in machine words, and a value to OR, -- atomically OR the value into the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) -- | Given an array, and offset in machine words, and a value to NAND, -- atomically NAND the value into the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) -- | Given an array, and offset in machine words, and a value to AND, -- atomically AND the value into the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) -- | Given an array, and offset in machine words, and a value to subtract, -- atomically subtract the value from the element. Returns the value of -- the element before the operation. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) -- | Given an array, and offset in machine words, and a value to add, -- atomically add the value to the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) -- | Given an array, an offset in 64 bit units, the expected old value, and -- the new value, perform an atomic compare and swap i.e. write the new -- value if the current value matches the provided old value. Returns the -- value of the element before the operation. Implies a full memory -- barrier. -- -- Warning: this can fail with an unchecked exception. casInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #) -- | Given an array, an offset in 32 bit units, the expected old value, and -- the new value, perform an atomic compare and swap i.e. write the new -- value if the current value matches the provided old value. Returns the -- value of the element before the operation. Implies a full memory -- barrier. -- -- Warning: this can fail with an unchecked exception. casInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #) -- | Given an array, an offset in 16 bit units, the expected old value, and -- the new value, perform an atomic compare and swap i.e. write the new -- value if the current value matches the provided old value. Returns the -- value of the element before the operation. Implies a full memory -- barrier. -- -- Warning: this can fail with an unchecked exception. casInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #) -- | Given an array, an offset in bytes, the expected old value, and the -- new value, perform an atomic compare and swap i.e. write the new value -- if the current value matches the provided old value. Returns the value -- of the element before the operation. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. casInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #) -- | Given an array, an offset in machine words, the expected old value, -- and the new value, perform an atomic compare and swap i.e. write the -- new value if the current value matches the provided old value. Returns -- the value of the element before the operation. Implies a full memory -- barrier. -- -- Warning: this can fail with an unchecked exception. casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #) -- | Given an array and an offset in machine words, write an element. The -- index is assumed to be in bounds. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Given an array and an offset in machine words, read an element. The -- index is assumed to be in bounds. Implies a full memory barrier. -- -- Warning: this can fail with an unchecked exception. atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | setAddrRange# dest len c sets all of the bytes in -- [dest, dest+len) to the value c. -- -- Analogous to the standard C function memset, but with a -- different argument order. -- -- Warning: this can fail with an unchecked exception. setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld -- | setByteArray# ba off len c sets the byte range -- [off, off+len) of the MutableByteArray# to the byte -- c. -- -- Warning: this can fail with an unchecked exception. setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d -- | copyAddrToAddrNonOverlapping# src dest len copies -- len bytes from src to dest. As the name -- suggests, these two memory ranges must not overlap, although -- this pre-condition is not checked. -- -- Analogous to the standard C function memcpy, but with a -- different argument order. -- -- Warning: this can fail with an unchecked exception. copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld -- | copyAddrToAddr# src dest len copies len bytes -- from src to dest. These two memory ranges are -- allowed to overlap. -- -- Analogous to the standard C function memmove, but with a -- different argument order. -- -- Warning: this can fail with an unchecked exception. copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld -- | Copy a memory range starting at the Addr# to the specified range in -- the MutableByteArray#. The memory region at Addr# and the ByteArray# -- must fully contain the specified ranges, but this is not checked. The -- Addr# must not point into the MutableByteArray# (e.g. if the -- MutableByteArray# were pinned), but this is not checked either. -- -- Warning: this can fail with an unchecked exception. copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Copy a range of the MutableByteArray# to the memory range starting at -- the Addr#. The MutableByteArray# and the memory region at Addr# must -- fully contain the specified ranges, but this is not checked. The Addr# -- must not point into the MutableByteArray# (e.g. if the -- MutableByteArray# were pinned), but this is not checked either. -- -- Warning: this can fail with an unchecked exception. copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d -- | Copy a range of the ByteArray# to the memory range starting at the -- Addr#. The ByteArray# and the memory region at Addr# must fully -- contain the specified ranges, but this is not checked. The Addr# must -- not point into the ByteArray# (e.g. if the ByteArray# were pinned), -- but this is not checked either. -- -- Warning: this can fail with an unchecked exception. copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d -- | copyMutableByteArrayNonOverlapping# src src_ofs dst dst_ofs -- len copies the range starting at offset src_ofs of -- length len from the MutableByteArray# src to -- the MutableByteArray# dst starting at offset -- dst_ofs. Both arrays must fully contain the specified ranges, -- but this is not checked. The regions are not allowed to -- overlap, but this is also not checked. -- -- Warning: this can fail with an unchecked exception. copyMutableByteArrayNonOverlapping# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | copyMutableByteArray# src src_ofs dst dst_ofs len -- copies the range starting at offset src_ofs of length -- len from the MutableByteArray# src to the -- MutableByteArray# dst starting at offset -- dst_ofs. Both arrays must fully contain the specified ranges, -- but this is not checked. The regions are allowed to overlap, although -- this is only possible when the same array is provided as both the -- source and the destination. -- -- Warning: this can fail with an unchecked exception. copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | copyByteArray# src src_ofs dst dst_ofs len copies the -- range starting at offset src_ofs of length len from -- the ByteArray# src to the MutableByteArray# -- dst starting at offset dst_ofs. Both arrays must -- fully contain the specified ranges, but this is not checked. The two -- arrays must not be the same array in different states, but this is not -- checked either. -- -- Warning: this can fail with an unchecked exception. copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | compareByteArrays# src1 src1_ofs src2 src2_ofs n -- compares n bytes starting at offset src1_ofs in the -- first ByteArray# src1 to the range of n bytes -- (i.e. same length) starting at offset src2_ofs of the second -- ByteArray# src2. Both arrays must fully contain the -- specified ranges, but this is not checked. Returns an Int# less -- than, equal to, or greater than zero if the range is found, -- respectively, to be byte-wise lexicographically less than, to match, -- or be greater than the second range. -- -- Warning: this can fail with an unchecked exception. compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# -- | Write a 64-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d -- | Write a 64-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d -- | Write a 32-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d -- | Write a 32-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d -- | Write a 16-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d -- | Write a 16-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d -- | Write a StablePtr# value; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d -- | Write a double-precision floating-point value; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d -- | Write a single-precision floating-point value; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d -- | Write a machine address; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d -- | Write a word-sized unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Write a word-sized integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Write a 32-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d -- | Write an 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d -- | Write a 64-bit unsigned integer; offset in 8-byte words. -- -- Warning: this can fail with an unchecked exception. writeWord64Array# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d -- | Write a 64-bit signed integer; offset in 8-byte words. -- -- Warning: this can fail with an unchecked exception. writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d -- | Write a 32-bit unsigned integer; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. writeWord32Array# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d -- | Write a 32-bit signed integer; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. writeInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d -- | Write a 16-bit unsigned integer; offset in 2-byte words. -- -- Warning: this can fail with an unchecked exception. writeWord16Array# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d -- | Write a 16-bit signed integer; offset in 2-byte words. -- -- Warning: this can fail with an unchecked exception. writeInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d -- | Write an 8-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d -- | Write an 8-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d -- | Write a StablePtr# value; offset in machine words. -- -- Warning: this can fail with an unchecked exception. writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d -- | Write a double-precision floating-point value; offset in 8-byte words. -- -- Warning: this can fail with an unchecked exception. writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d -- | Write a single-precision floating-point value; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d -- | Write a machine address; offset in machine words. -- -- Warning: this can fail with an unchecked exception. writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d -- | Write a word-sized unsigned integer; offset in machine words. -- -- Warning: this can fail with an unchecked exception. writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Write a word-sized integer; offset in machine words. -- -- Warning: this can fail with an unchecked exception. writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Write a 32-bit character; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d -- | Write an 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d -- | Read a 64-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) -- | Read a 64-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) -- | Read a 32-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) -- | Read a 32-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) -- | Read a 16-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) -- | Read a 16-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) -- | Read a StablePtr# value; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) -- | Read a double-precision floating-point value; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) -- | Read a single-precision floating-point value; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) -- | Read a machine address; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) -- | Read a word-sized unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Read a word-sized integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Read a 32-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) -- | Read an 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) -- | Read a 64-bit unsigned integer; offset in 8-byte words. -- -- Warning: this can fail with an unchecked exception. readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) -- | Read a 64-bit signed integer; offset in 8-byte words. -- -- Warning: this can fail with an unchecked exception. readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) -- | Read a 32-bit unsigned integer; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) -- | Read a 32-bit signed integer; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) -- | Read a 16-bit unsigned integer; offset in 2-byte words. -- -- Warning: this can fail with an unchecked exception. readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) -- | Read a 16-bit signed integer; offset in 2-byte words. -- -- Warning: this can fail with an unchecked exception. readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) -- | Read an 8-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #) -- | Read an 8-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #) -- | Read a StablePtr# value; offset in machine words. -- -- Warning: this can fail with an unchecked exception. readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) -- | Read a double-precision floating-point value; offset in 8-byte words. -- -- Warning: this can fail with an unchecked exception. readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) -- | Read a single-precision floating-point value; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) -- | Read a machine address; offset in machine words. -- -- Warning: this can fail with an unchecked exception. readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) -- | Read a word-sized unsigned integer; offset in machine words. -- -- Warning: this can fail with an unchecked exception. readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Read a word-sized integer; offset in machine words. -- -- Warning: this can fail with an unchecked exception. readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Read a 32-bit character; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) -- | Read an 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) -- | Read a 64-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64# -- | Read a 64-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64# -- | Read a 32-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32# -- | Read a 32-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32# -- | Read a 16-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16# -- | Read a 16-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16# -- | Read a StablePtr# value; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a -- | Read a double-precision floating-point value; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# -- | Read a single-precision floating-point value; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# -- | Read a machine address; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# -- | Read a word-sized unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# -- | Read a word-sized integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# -- | Read a 32-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# -- | Read an 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# -- | Read a 64-bit unsigned integer; offset in 8-byte words. -- -- Warning: this can fail with an unchecked exception. indexWord64Array# :: ByteArray# -> Int# -> Word64# -- | Read a 64-bit signed integer; offset in 8-byte words. -- -- Warning: this can fail with an unchecked exception. indexInt64Array# :: ByteArray# -> Int# -> Int64# -- | Read a 32-bit unsigned integer; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. indexWord32Array# :: ByteArray# -> Int# -> Word32# -- | Read a 32-bit signed integer; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. indexInt32Array# :: ByteArray# -> Int# -> Int32# -- | Read a 16-bit unsigned integer; offset in 2-byte words. -- -- Warning: this can fail with an unchecked exception. indexWord16Array# :: ByteArray# -> Int# -> Word16# -- | Read a 16-bit signed integer; offset in 2-byte words. -- -- Warning: this can fail with an unchecked exception. indexInt16Array# :: ByteArray# -> Int# -> Int16# -- | Read an 8-bit unsigned integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8Array# :: ByteArray# -> Int# -> Word8# -- | Read an 8-bit signed integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexInt8Array# :: ByteArray# -> Int# -> Int8# -- | Read a StablePtr# value; offset in machine words. -- -- Warning: this can fail with an unchecked exception. indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a -- | Read a double-precision floating-point value; offset in 8-byte words. -- -- Warning: this can fail with an unchecked exception. indexDoubleArray# :: ByteArray# -> Int# -> Double# -- | Read a single-precision floating-point value; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. indexFloatArray# :: ByteArray# -> Int# -> Float# -- | Read a machine address; offset in machine words. -- -- Warning: this can fail with an unchecked exception. indexAddrArray# :: ByteArray# -> Int# -> Addr# -- | Read a word-sized unsigned integer; offset in machine words. -- -- Warning: this can fail with an unchecked exception. indexWordArray# :: ByteArray# -> Int# -> Word# -- | Read a word-sized integer; offset in machine words. -- -- Warning: this can fail with an unchecked exception. indexIntArray# :: ByteArray# -> Int# -> Int# -- | Read a 32-bit character; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. indexWideCharArray# :: ByteArray# -> Int# -> Char# -- | Read an 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexCharArray# :: ByteArray# -> Int# -> Char# -- | Return the number of elements in the array, correctly accounting for -- the effect of shrinkMutableByteArray# and -- resizeMutableByteArray#. getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #) -- | Return the size of the array in bytes. Deprecated, it is unsafe -- in the presence of shrinkMutableByteArray# and -- resizeMutableByteArray# operations on the same mutable byte -- array. sizeofMutableByteArray# :: MutableByteArray# d -> Int# -- | Return the size of the array in bytes. sizeofByteArray# :: ByteArray# -> Int# -- | Make a mutable byte array immutable, without copying. unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) -- | Resize mutable byte array to new specified size (in bytes), shrinking -- or growing it. The returned MutableByteArray# is either the -- original MutableByteArray# resized in-place or, if not -- possible, a newly allocated (unpinned) MutableByteArray# (with -- the original content copied over). -- -- To avoid undefined behaviour, the original MutableByteArray# -- shall not be accessed anymore after a resizeMutableByteArray# -- has been performed. Moreover, no reference to the old one should be -- kept in order to allow garbage collection of the original -- MutableByteArray# in case a new MutableByteArray# had to -- be allocated. resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #) -- | Shrink mutable byte array to new specified size (in bytes), in the -- specified state thread. The new size argument must be less than or -- equal to the current size as reported by -- getSizeofMutableByteArray#. -- -- Assuming the non-profiling RTS, this primitive compiles to an O(1) -- operation in C--, modifying the array in-place. Backends bypassing C-- -- representation (such as JavaScript) might behave differently. shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d -- | Intended for use with pinned arrays; otherwise very unsafe! mutableByteArrayContents# :: MutableByteArray# d -> Addr# -- | Intended for use with pinned arrays; otherwise very unsafe! byteArrayContents# :: ByteArray# -> Addr# -- | Determine whether a ByteArray# is guaranteed not to move during -- GC. isByteArrayPinned# :: ByteArray# -> Int# -- | Determine whether a MutableByteArray# is guaranteed not to move -- during GC. isMutableByteArrayPinned# :: MutableByteArray# d -> Int# -- | Like newPinnedByteArray# but allow specifying an arbitrary -- alignment, which must be a power of two. newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) -- | Like newByteArray# but GC guarantees not to move it. newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) -- | Create a new mutable byte array of specified size (in bytes), in the -- specified state thread. The size of the memory underlying the array -- will be rounded up to the platform's word size. newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) -- | Unsafe, machine-level atomic compare and swap on an element within an -- array. See the documentation of casArray#. -- -- Warning: this can fail with an unchecked exception. casSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) -- | Given a source array, an offset into the source array, and a number of -- elements to copy, create a new array with the elements from the source -- array. The provided array must fully contain the specified range, but -- this is not checked. -- -- Warning: this can fail with an unchecked exception. thawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) -- | Given a source array, an offset into the source array, and a number of -- elements to copy, create a new array with the elements from the source -- array. The provided array must fully contain the specified range, but -- this is not checked. -- -- Warning: this can fail with an unchecked exception. freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #) -- | Given a source array, an offset into the source array, and a number of -- elements to copy, create a new array with the elements from the source -- array. The provided array must fully contain the specified range, but -- this is not checked. -- -- Warning: this can fail with an unchecked exception. cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) -- | Given a source array, an offset into the source array, and a number of -- elements to copy, create a new array with the elements from the source -- array. The provided array must fully contain the specified range, but -- this is not checked. -- -- Warning: this can fail with an unchecked exception. cloneSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a -- | Given a source array, an offset into the source array, a destination -- array, an offset into the destination array, and a number of elements -- to copy, copy the elements from the source array to the destination -- array. The source and destination arrays can refer to the same array. -- Both arrays must fully contain the specified ranges, but this is not -- checked. The regions are allowed to overlap, although this is only -- possible when the same array is provided as both the source and the -- destination. -- -- Warning: this can fail with an unchecked exception. copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d -- | Given a source array, an offset into the source array, a destination -- array, an offset into the destination array, and a number of elements -- to copy, copy the elements from the source array to the destination -- array. Both arrays must fully contain the specified ranges, but this -- is not checked. The two arrays must not be the same array in different -- states, but this is not checked either. -- -- Warning: this can fail with an unchecked exception. copySmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d -- | Make an immutable array mutable, without copying. unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #) -- | Make a mutable array immutable, without copying. unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #) -- | Read from specified index of immutable array. Result is packaged into -- an unboxed singleton; the result itself is not yet evaluated. -- -- Warning: this can fail with an unchecked exception. indexSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> (# a #) -- | Return the number of elements in the array, correctly accounting for -- the effect of shrinkSmallMutableArray# and -- resizeSmallMutableArray#. getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #) -- | Return the number of elements in the array. Deprecated, it is -- unsafe in the presence of shrinkSmallMutableArray# and -- resizeSmallMutableArray# operations on the same small mutable -- array. sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -- | Return the number of elements in the array. sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -- | Write to specified index of mutable array. -- -- Warning: this can fail with an unchecked exception. writeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d -- | Read from specified index of mutable array. Result is not yet -- evaluated. -- -- Warning: this can fail with an unchecked exception. readSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #) -- | Shrink mutable array to new specified size, in the specified state -- thread. The new size argument must be less than or equal to the -- current size as reported by getSizeofSmallMutableArray#. -- -- Assuming the non-profiling RTS, for the copying garbage collector -- (default) this primitive compiles to an O(1) operation in C--, -- modifying the array in-place. For the non-moving garbage collector, -- however, the time is proportional to the number of elements shrinked -- out. Backends bypassing C-- representation (such as JavaScript) might -- behave differently. shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d -- | Create a new mutable array with the specified number of elements, in -- the specified state thread, with each element containing the specified -- initial value. newSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #) -- | Given an array, an offset, the expected old value, and the new value, -- perform an atomic compare and swap (i.e. write the new value if the -- current value and the old value are the same pointer). Returns 0 if -- the swap succeeds and 1 if it fails. Additionally, returns the element -- at the offset after the operation completes. This means that on a -- success the new value is returned, and on a failure the actual old -- value (not the expected one) is returned. Implies a full memory -- barrier. The use of a pointer equality on a boxed value makes this -- function harder to use correctly than casIntArray#. All of the -- difficulties of using reallyUnsafePtrEquality# correctly apply -- to casArray# as well. -- -- Warning: this can fail with an unchecked exception. casArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) -- | Given a source array, an offset into the source array, and a number of -- elements to copy, create a new array with the elements from the source -- array. The provided array must fully contain the specified range, but -- this is not checked. -- -- Warning: this can fail with an unchecked exception. thawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) -- | Given a source array, an offset into the source array, and a number of -- elements to copy, create a new array with the elements from the source -- array. The provided array must fully contain the specified range, but -- this is not checked. -- -- Warning: this can fail with an unchecked exception. freezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #) -- | Given a source array, an offset into the source array, and a number of -- elements to copy, create a new array with the elements from the source -- array. The provided array must fully contain the specified range, but -- this is not checked. -- -- Warning: this can fail with an unchecked exception. cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) -- | Given a source array, an offset into the source array, and a number of -- elements to copy, create a new array with the elements from the source -- array. The provided array must fully contain the specified range, but -- this is not checked. -- -- Warning: this can fail with an unchecked exception. cloneArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> Int# -> Array# a -- | Given a source array, an offset into the source array, a destination -- array, an offset into the destination array, and a number of elements -- to copy, copy the elements from the source array to the destination -- array. Both arrays must fully contain the specified ranges, but this -- is not checked. In the case where the source and destination are the -- same array the source and destination regions may overlap. -- -- Warning: this can fail with an unchecked exception. copyMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d -- | Given a source array, an offset into the source array, a destination -- array, an offset into the destination array, and a number of elements -- to copy, copy the elements from the source array to the destination -- array. Both arrays must fully contain the specified ranges, but this -- is not checked. The two arrays must not be the same array in different -- states, but this is not checked either. -- -- Warning: this can fail with an unchecked exception. copyArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d -- | Make an immutable array mutable, without copying. unsafeThawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #) -- | Make a mutable array immutable, without copying. unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #) -- | Read from the specified index of an immutable array. The result is -- packaged into an unboxed unary tuple; the result itself is not yet -- evaluated. Pattern matching on the tuple forces the indexing of the -- array to happen but does not evaluate the element itself. Evaluating -- the thunk prevents additional thunks from building up on the heap. -- Avoiding these thunks, in turn, reduces references to the argument -- array, allowing it to be garbage collected more promptly. -- -- Warning: this can fail with an unchecked exception. indexArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> (# a #) -- | Return the number of elements in the array. sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -- | Return the number of elements in the array. sizeofArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -- | Write to specified index of mutable array. -- -- Warning: this can fail with an unchecked exception. writeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d -- | Read from specified index of mutable array. Result is not yet -- evaluated. -- -- Warning: this can fail with an unchecked exception. readArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #) -- | Create a new mutable array with the specified number of elements, in -- the specified state thread, with each element containing the specified -- initial value. newArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) -- | Fused negate-multiply-subtract operation -x*y-z. See -- GHC.Prim#fma. fnmsubDouble# :: Double# -> Double# -> Double# -> Double# -- | Fused negate-multiply-add operation -x*y+z. See -- GHC.Prim#fma. fnmaddDouble# :: Double# -> Double# -> Double# -> Double# -- | Fused multiply-subtract operation x*y-z. See -- GHC.Prim#fma. fmsubDouble# :: Double# -> Double# -> Double# -> Double# -- | Fused multiply-add operation x*y+z. See GHC.Prim#fma. fmaddDouble# :: Double# -> Double# -> Double# -> Double# -- | Fused negate-multiply-subtract operation -x*y-z. See -- GHC.Prim#fma. fnmsubFloat# :: Float# -> Float# -> Float# -> Float# -- | Fused negate-multiply-add operation -x*y+z. See -- GHC.Prim#fma. fnmaddFloat# :: Float# -> Float# -> Float# -> Float# -- | Fused multiply-subtract operation x*y-z. See -- GHC.Prim#fma. fmsubFloat# :: Float# -> Float# -> Float# -> Float# -- | Fused multiply-add operation x*y+z. See GHC.Prim#fma. fmaddFloat# :: Float# -> Float# -> Float# -> Float# -- | Convert to integers. First Int# in result is the mantissa; -- second is the exponent. decodeFloat_Int# :: Float# -> (# Int#, Int# #) float2Double# :: Float# -> Double# powerFloat# :: Float# -> Float# -> Float# atanhFloat# :: Float# -> Float# acoshFloat# :: Float# -> Float# asinhFloat# :: Float# -> Float# tanhFloat# :: Float# -> Float# coshFloat# :: Float# -> Float# sinhFloat# :: Float# -> Float# atanFloat# :: Float# -> Float# -- | Warning: this can fail with an unchecked exception. acosFloat# :: Float# -> Float# -- | Warning: this can fail with an unchecked exception. asinFloat# :: Float# -> Float# tanFloat# :: Float# -> Float# cosFloat# :: Float# -> Float# sinFloat# :: Float# -> Float# sqrtFloat# :: Float# -> Float# -- | Warning: this can fail with an unchecked exception. log1pFloat# :: Float# -> Float# -- | Warning: this can fail with an unchecked exception. logFloat# :: Float# -> Float# expm1Float# :: Float# -> Float# expFloat# :: Float# -> Float# -- | Truncates a Float# value to the nearest Int#. Results -- are undefined if the truncation if truncation yields a value outside -- the range of Int#. float2Int# :: Float# -> Int# fabsFloat# :: Float# -> Float# negateFloat# :: Float# -> Float# -- | Warning: this can fail with an unchecked exception. divideFloat# :: Float# -> Float# -> Float# timesFloat# :: Float# -> Float# -> Float# minusFloat# :: Float# -> Float# -> Float# plusFloat# :: Float# -> Float# -> Float# leFloat# :: Float# -> Float# -> Int# ltFloat# :: Float# -> Float# -> Int# neFloat# :: Float# -> Float# -> Int# eqFloat# :: Float# -> Float# -> Int# geFloat# :: Float# -> Float# -> Int# gtFloat# :: Float# -> Float# -> Int# -- | Decode Double# into mantissa and base-2 exponent. decodeDouble_Int64# :: Double# -> (# Int64#, Int# #) -- | Convert to integer. First component of the result is -1 or 1, -- indicating the sign of the mantissa. The next two are the high and low -- 32 bits of the mantissa respectively, and the last is the exponent. decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #) -- | Exponentiation. (**##) :: Double# -> Double# -> Double# atanhDouble# :: Double# -> Double# acoshDouble# :: Double# -> Double# asinhDouble# :: Double# -> Double# tanhDouble# :: Double# -> Double# coshDouble# :: Double# -> Double# sinhDouble# :: Double# -> Double# atanDouble# :: Double# -> Double# -- | Warning: this can fail with an unchecked exception. acosDouble# :: Double# -> Double# -- | Warning: this can fail with an unchecked exception. asinDouble# :: Double# -> Double# tanDouble# :: Double# -> Double# cosDouble# :: Double# -> Double# sinDouble# :: Double# -> Double# sqrtDouble# :: Double# -> Double# -- | Warning: this can fail with an unchecked exception. log1pDouble# :: Double# -> Double# -- | Warning: this can fail with an unchecked exception. logDouble# :: Double# -> Double# expm1Double# :: Double# -> Double# expDouble# :: Double# -> Double# double2Float# :: Double# -> Float# -- | Truncates a Double# value to the nearest Int#. Results -- are undefined if the truncation if truncation yields a value outside -- the range of Int#. double2Int# :: Double# -> Int# fabsDouble# :: Double# -> Double# negateDouble# :: Double# -> Double# -- | Warning: this can fail with an unchecked exception. (/##) :: Double# -> Double# -> Double# infixl 7 /## (*##) :: Double# -> Double# -> Double# infixl 7 *## (-##) :: Double# -> Double# -> Double# infixl 6 -## (+##) :: Double# -> Double# -> Double# infixl 6 +## (<=##) :: Double# -> Double# -> Int# infix 4 <=## (<##) :: Double# -> Double# -> Int# infix 4 <## (/=##) :: Double# -> Double# -> Int# infix 4 /=## (==##) :: Double# -> Double# -> Int# infix 4 ==## (>=##) :: Double# -> Double# -> Int# infix 4 >=## (>##) :: Double# -> Double# -> Int# infix 4 >## narrow32Word# :: Word# -> Word# narrow16Word# :: Word# -> Word# narrow8Word# :: Word# -> Word# narrow32Int# :: Int# -> Int# narrow16Int# :: Int# -> Int# narrow8Int# :: Int# -> Int# -- | Reverse the order of the bits in a word. bitReverse# :: Word# -> Word# -- | Reverse the order of the bits in a 64-bit word. bitReverse64# :: Word64# -> Word64# -- | Reverse the order of the bits in a 32-bit word. bitReverse32# :: Word# -> Word# -- | Reverse the order of the bits in a 16-bit word. bitReverse16# :: Word# -> Word# -- | Reverse the order of the bits in a 8-bit word. bitReverse8# :: Word# -> Word# -- | Swap bytes in a word. byteSwap# :: Word# -> Word# -- | Swap bytes in a 64 bits of a word. byteSwap64# :: Word64# -> Word64# -- | Swap bytes in the lower 32 bits of a word. The higher bytes are -- undefined. byteSwap32# :: Word# -> Word# -- | Swap bytes in the lower 16 bits of a word. The higher bytes are -- undefined. byteSwap16# :: Word# -> Word# -- | Count trailing zeros in a word. ctz# :: Word# -> Word# -- | Count trailing zeros in a 64-bit word. ctz64# :: Word64# -> Word# -- | Count trailing zeros in the lower 32 bits of a word. ctz32# :: Word# -> Word# -- | Count trailing zeros in the lower 16 bits of a word. ctz16# :: Word# -> Word# -- | Count trailing zeros in the lower 8 bits of a word. ctz8# :: Word# -> Word# -- | Count leading zeros in a word. clz# :: Word# -> Word# -- | Count leading zeros in a 64-bit word. clz64# :: Word64# -> Word# -- | Count leading zeros in the lower 32 bits of a word. clz32# :: Word# -> Word# -- | Count leading zeros in the lower 16 bits of a word. clz16# :: Word# -> Word# -- | Count leading zeros in the lower 8 bits of a word. clz8# :: Word# -> Word# -- | Extract bits from a word at locations specified by a mask, aka -- parallel bit extract. -- -- Software emulation: -- --
--   pext :: Word -> Word -> Word
--   pext src mask = loop 0 0 0
--     where
--       loop i count result
--         | i >= finiteBitSize (0 :: Word)
--         = result
--         | testBit mask i
--         = loop (i + 1) (count + 1) (if testBit src i then setBit result count else result)
--         | otherwise
--         = loop (i + 1) count result
--   
pext# :: Word# -> Word# -> Word# -- | Extract bits from a word at locations specified by a mask. pext64# :: Word64# -> Word64# -> Word64# -- | Extract bits from lower 32 bits of a word at locations specified by a -- mask. pext32# :: Word# -> Word# -> Word# -- | Extract bits from lower 16 bits of a word at locations specified by a -- mask. pext16# :: Word# -> Word# -> Word# -- | Extract bits from lower 8 bits of a word at locations specified by a -- mask. pext8# :: Word# -> Word# -> Word# -- | Deposit bits to a word at locations specified by a mask, aka -- parallel bit deposit. -- -- Software emulation: -- --
--   pdep :: Word -> Word -> Word
--   pdep src mask = go 0 src mask
--     where
--       go :: Word -> Word -> Word -> Word
--       go result _ 0 = result
--       go result src mask = go newResult newSrc newMask
--         where
--           maskCtz   = countTrailingZeros mask
--           newResult = if testBit src 0 then setBit result maskCtz else result
--           newSrc    = src `shiftR` 1
--           newMask   = clearBit mask maskCtz
--   
pdep# :: Word# -> Word# -> Word# -- | Deposit bits to a word at locations specified by a mask. pdep64# :: Word64# -> Word64# -> Word64# -- | Deposit bits to lower 32 bits of a word at locations specified by a -- mask. pdep32# :: Word# -> Word# -> Word# -- | Deposit bits to lower 16 bits of a word at locations specified by a -- mask. pdep16# :: Word# -> Word# -> Word# -- | Deposit bits to lower 8 bits of a word at locations specified by a -- mask. pdep8# :: Word# -> Word# -> Word# -- | Count the number of set bits in a word. popCnt# :: Word# -> Word# -- | Count the number of set bits in a 64-bit word. popCnt64# :: Word64# -> Word# -- | Count the number of set bits in the lower 32 bits of a word. popCnt32# :: Word# -> Word# -- | Count the number of set bits in the lower 16 bits of a word. popCnt16# :: Word# -> Word# -- | Count the number of set bits in the lower 8 bits of a word. popCnt8# :: Word# -> Word# leWord# :: Word# -> Word# -> Int# ltWord# :: Word# -> Word# -> Int# neWord# :: Word# -> Word# -> Int# eqWord# :: Word# -> Word# -> Int# geWord# :: Word# -> Word# -> Int# gtWord# :: Word# -> Word# -> Int# word2Int# :: Word# -> Int# -- | Shift right logical. Result undefined if shift amount is not in the -- range 0 to word size - 1 inclusive. uncheckedShiftRL# :: Word# -> Int# -> Word# -- | Shift left logical. Result undefined if shift amount is not in the -- range 0 to word size - 1 inclusive. uncheckedShiftL# :: Word# -> Int# -> Word# not# :: Word# -> Word# xor# :: Word# -> Word# -> Word# or# :: Word# -> Word# -> Word# and# :: Word# -> Word# -> Word# -- | Takes high word of dividend, then low word of dividend, then divisor. -- Requires that high word < divisor. -- -- Warning: this can fail with an unchecked exception. quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #) -- | Warning: this can fail with an unchecked exception. quotRemWord# :: Word# -> Word# -> (# Word#, Word# #) -- | Warning: this can fail with an unchecked exception. remWord# :: Word# -> Word# -> Word# -- | Warning: this can fail with an unchecked exception. quotWord# :: Word# -> Word# -> Word# timesWord2# :: Word# -> Word# -> (# Word#, Word# #) timesWord# :: Word# -> Word# -> Word# minusWord# :: Word# -> Word# -> Word# -- | Add unsigned integers, with the high part (carry) in the first -- component of the returned pair and the low part in the second -- component of the pair. See also addWordC#. plusWord2# :: Word# -> Word# -> (# Word#, Word# #) -- | Subtract unsigned integers reporting overflow. The first element of -- the pair is the result. The second element is the carry flag, which is -- nonzero on overflow. subWordC# :: Word# -> Word# -> (# Word#, Int# #) -- | Add unsigned integers reporting overflow. The first element of the -- pair is the result. The second element is the carry flag, which is -- nonzero on overflow. See also plusWord2#. addWordC# :: Word# -> Word# -> (# Word#, Int# #) plusWord# :: Word# -> Word# -> Word# -- | Shift right logical. Result undefined if shift amount is not in the -- range 0 to word size - 1 inclusive. uncheckedIShiftRL# :: Int# -> Int# -> Int# -- | Shift right arithmetic. Result undefined if shift amount is not in the -- range 0 to word size - 1 inclusive. uncheckedIShiftRA# :: Int# -> Int# -> Int# -- | Shift left. Result undefined if shift amount is not in the range 0 to -- word size - 1 inclusive. uncheckedIShiftL# :: Int# -> Int# -> Int# -- | Convert an Word# to the corresponding Double# with the -- same integral value (up to truncation due to floating-point -- precision). e.g. word2Double# 1## == 1.0## word2Double# :: Word# -> Double# -- | Convert an Word# to the corresponding Float# with the -- same integral value (up to truncation due to floating-point -- precision). e.g. word2Float# 1## == 1.0# word2Float# :: Word# -> Float# -- | Convert an Int# to the corresponding Double# with the -- same integral value (up to truncation due to floating-point -- precision). e.g. int2Double# 1# == 1.0## int2Double# :: Int# -> Double# -- | Convert an Int# to the corresponding Float# with the -- same integral value (up to truncation due to floating-point -- precision). e.g. int2Float# 1# == 1.0# int2Float# :: Int# -> Float# int2Word# :: Int# -> Word# chr# :: Int# -> Char# (<=#) :: Int# -> Int# -> Int# infix 4 <=# (<#) :: Int# -> Int# -> Int# infix 4 <# (/=#) :: Int# -> Int# -> Int# infix 4 /=# (==#) :: Int# -> Int# -> Int# infix 4 ==# (>=#) :: Int# -> Int# -> Int# infix 4 >=# (>#) :: Int# -> Int# -> Int# infix 4 ># -- | Subtract signed integers reporting overflow. First member of result is -- the difference truncated to an Int#; second member is zero if -- the true difference fits in an Int#, nonzero if overflow -- occurred (the difference is either too large or too small to fit in an -- Int#). subIntC# :: Int# -> Int# -> (# Int#, Int# #) -- | Add signed integers reporting overflow. First member of result is the -- sum truncated to an Int#; second member is zero if the true sum -- fits in an Int#, nonzero if overflow occurred (the sum is -- either too large or too small to fit in an Int#). addIntC# :: Int# -> Int# -> (# Int#, Int# #) -- | Unary negation. Since the negative Int# range extends one -- further than the positive range, negateInt# of the most -- negative number is an identity operation. This way, negateInt# -- is always its own inverse. negateInt# :: Int# -> Int# -- | Bitwise "not", also known as the binary complement. notI# :: Int# -> Int# -- | Bitwise "xor". xorI# :: Int# -> Int# -> Int# -- | Bitwise "or". orI# :: Int# -> Int# -> Int# -- | Bitwise "and". andI# :: Int# -> Int# -> Int# -- | Rounds towards zero. -- -- Warning: this can fail with an unchecked exception. quotRemInt# :: Int# -> Int# -> (# Int#, Int# #) -- | Satisfies (quotInt# x y) *# y +# -- (remInt# x y) == x. The behavior is undefined if the -- second argument is zero. -- -- Warning: this can fail with an unchecked exception. remInt# :: Int# -> Int# -> Int# -- | Rounds towards zero. The behavior is undefined if the second argument -- is zero. -- -- Warning: this can fail with an unchecked exception. quotInt# :: Int# -> Int# -> Int# -- | Return non-zero if there is any possibility that the upper word of a -- signed integer multiply might contain useful information. Return zero -- only if you are completely sure that no overflow can occur. On a -- 32-bit platform, the recommended implementation is to do a 32 x 32 -- -> 64 signed multiply, and subtract result[63:32] from (result[31] -- >>signed 31). If this is zero, meaning that the upper word is -- merely a sign extension of the lower one, no overflow can occur. -- -- On a 64-bit platform it is not always possible to acquire the top 64 -- bits of the result. Therefore, a recommended implementation is to take -- the absolute value of both operands, and return 0 iff bits[63:31] of -- them are zero, since that means that their magnitudes fit within 31 -- bits, so the magnitude of the product must fit into 62 bits. -- -- If in doubt, return non-zero, but do make an effort to create the -- correct answer for small args, since otherwise the performance of -- (*) :: Integer -> Integer -> Integer will be poor. mulIntMayOflo# :: Int# -> Int# -> Int# -- | Return a triple (isHighNeeded,high,low) where high and low are -- respectively the high and low bits of the double-word result. -- isHighNeeded is a cheap way to test if the high word is a -- sign-extension of the low word (isHighNeeded = 0#) or not -- (isHighNeeded = 1#). timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #) -- | Low word of signed integer multiply. (*#) :: Int# -> Int# -> Int# infixl 7 *# (-#) :: Int# -> Int# -> Int# infixl 6 -# (+#) :: Int# -> Int# -> Int# infixl 6 +# neWord64# :: Word64# -> Word64# -> Int# ltWord64# :: Word64# -> Word64# -> Int# leWord64# :: Word64# -> Word64# -> Int# gtWord64# :: Word64# -> Word64# -> Int# geWord64# :: Word64# -> Word64# -> Int# eqWord64# :: Word64# -> Word64# -> Int# word64ToInt64# :: Word64# -> Int64# uncheckedShiftRL64# :: Word64# -> Int# -> Word64# uncheckedShiftL64# :: Word64# -> Int# -> Word64# not64# :: Word64# -> Word64# xor64# :: Word64# -> Word64# -> Word64# or64# :: Word64# -> Word64# -> Word64# and64# :: Word64# -> Word64# -> Word64# -- | Warning: this can fail with an unchecked exception. remWord64# :: Word64# -> Word64# -> Word64# -- | Warning: this can fail with an unchecked exception. quotWord64# :: Word64# -> Word64# -> Word64# timesWord64# :: Word64# -> Word64# -> Word64# subWord64# :: Word64# -> Word64# -> Word64# plusWord64# :: Word64# -> Word64# -> Word64# wordToWord64# :: Word# -> Word64# word64ToWord# :: Word64# -> Word# neInt64# :: Int64# -> Int64# -> Int# ltInt64# :: Int64# -> Int64# -> Int# leInt64# :: Int64# -> Int64# -> Int# gtInt64# :: Int64# -> Int64# -> Int# geInt64# :: Int64# -> Int64# -> Int# eqInt64# :: Int64# -> Int64# -> Int# int64ToWord64# :: Int64# -> Word64# uncheckedIShiftRL64# :: Int64# -> Int# -> Int64# uncheckedIShiftRA64# :: Int64# -> Int# -> Int64# uncheckedIShiftL64# :: Int64# -> Int# -> Int64# -- | Warning: this can fail with an unchecked exception. remInt64# :: Int64# -> Int64# -> Int64# -- | Warning: this can fail with an unchecked exception. quotInt64# :: Int64# -> Int64# -> Int64# timesInt64# :: Int64# -> Int64# -> Int64# subInt64# :: Int64# -> Int64# -> Int64# plusInt64# :: Int64# -> Int64# -> Int64# negateInt64# :: Int64# -> Int64# intToInt64# :: Int# -> Int64# int64ToInt# :: Int64# -> Int# neWord32# :: Word32# -> Word32# -> Int# ltWord32# :: Word32# -> Word32# -> Int# leWord32# :: Word32# -> Word32# -> Int# gtWord32# :: Word32# -> Word32# -> Int# geWord32# :: Word32# -> Word32# -> Int# eqWord32# :: Word32# -> Word32# -> Int# word32ToInt32# :: Word32# -> Int32# uncheckedShiftRLWord32# :: Word32# -> Int# -> Word32# uncheckedShiftLWord32# :: Word32# -> Int# -> Word32# notWord32# :: Word32# -> Word32# xorWord32# :: Word32# -> Word32# -> Word32# orWord32# :: Word32# -> Word32# -> Word32# andWord32# :: Word32# -> Word32# -> Word32# -- | Warning: this can fail with an unchecked exception. quotRemWord32# :: Word32# -> Word32# -> (# Word32#, Word32# #) -- | Warning: this can fail with an unchecked exception. remWord32# :: Word32# -> Word32# -> Word32# -- | Warning: this can fail with an unchecked exception. quotWord32# :: Word32# -> Word32# -> Word32# timesWord32# :: Word32# -> Word32# -> Word32# subWord32# :: Word32# -> Word32# -> Word32# plusWord32# :: Word32# -> Word32# -> Word32# wordToWord32# :: Word# -> Word32# word32ToWord# :: Word32# -> Word# neInt32# :: Int32# -> Int32# -> Int# ltInt32# :: Int32# -> Int32# -> Int# leInt32# :: Int32# -> Int32# -> Int# gtInt32# :: Int32# -> Int32# -> Int# geInt32# :: Int32# -> Int32# -> Int# eqInt32# :: Int32# -> Int32# -> Int# int32ToWord32# :: Int32# -> Word32# uncheckedShiftRLInt32# :: Int32# -> Int# -> Int32# uncheckedShiftRAInt32# :: Int32# -> Int# -> Int32# uncheckedShiftLInt32# :: Int32# -> Int# -> Int32# -- | Warning: this can fail with an unchecked exception. quotRemInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #) -- | Warning: this can fail with an unchecked exception. remInt32# :: Int32# -> Int32# -> Int32# -- | Warning: this can fail with an unchecked exception. quotInt32# :: Int32# -> Int32# -> Int32# timesInt32# :: Int32# -> Int32# -> Int32# subInt32# :: Int32# -> Int32# -> Int32# plusInt32# :: Int32# -> Int32# -> Int32# negateInt32# :: Int32# -> Int32# intToInt32# :: Int# -> Int32# int32ToInt# :: Int32# -> Int# neWord16# :: Word16# -> Word16# -> Int# ltWord16# :: Word16# -> Word16# -> Int# leWord16# :: Word16# -> Word16# -> Int# gtWord16# :: Word16# -> Word16# -> Int# geWord16# :: Word16# -> Word16# -> Int# eqWord16# :: Word16# -> Word16# -> Int# word16ToInt16# :: Word16# -> Int16# uncheckedShiftRLWord16# :: Word16# -> Int# -> Word16# uncheckedShiftLWord16# :: Word16# -> Int# -> Word16# notWord16# :: Word16# -> Word16# xorWord16# :: Word16# -> Word16# -> Word16# orWord16# :: Word16# -> Word16# -> Word16# andWord16# :: Word16# -> Word16# -> Word16# -- | Warning: this can fail with an unchecked exception. quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #) -- | Warning: this can fail with an unchecked exception. remWord16# :: Word16# -> Word16# -> Word16# -- | Warning: this can fail with an unchecked exception. quotWord16# :: Word16# -> Word16# -> Word16# timesWord16# :: Word16# -> Word16# -> Word16# subWord16# :: Word16# -> Word16# -> Word16# plusWord16# :: Word16# -> Word16# -> Word16# wordToWord16# :: Word# -> Word16# word16ToWord# :: Word16# -> Word# neInt16# :: Int16# -> Int16# -> Int# ltInt16# :: Int16# -> Int16# -> Int# leInt16# :: Int16# -> Int16# -> Int# gtInt16# :: Int16# -> Int16# -> Int# geInt16# :: Int16# -> Int16# -> Int# eqInt16# :: Int16# -> Int16# -> Int# int16ToWord16# :: Int16# -> Word16# uncheckedShiftRLInt16# :: Int16# -> Int# -> Int16# uncheckedShiftRAInt16# :: Int16# -> Int# -> Int16# uncheckedShiftLInt16# :: Int16# -> Int# -> Int16# -- | Warning: this can fail with an unchecked exception. quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #) -- | Warning: this can fail with an unchecked exception. remInt16# :: Int16# -> Int16# -> Int16# -- | Warning: this can fail with an unchecked exception. quotInt16# :: Int16# -> Int16# -> Int16# timesInt16# :: Int16# -> Int16# -> Int16# subInt16# :: Int16# -> Int16# -> Int16# plusInt16# :: Int16# -> Int16# -> Int16# negateInt16# :: Int16# -> Int16# intToInt16# :: Int# -> Int16# int16ToInt# :: Int16# -> Int# neWord8# :: Word8# -> Word8# -> Int# ltWord8# :: Word8# -> Word8# -> Int# leWord8# :: Word8# -> Word8# -> Int# gtWord8# :: Word8# -> Word8# -> Int# geWord8# :: Word8# -> Word8# -> Int# eqWord8# :: Word8# -> Word8# -> Int# word8ToInt8# :: Word8# -> Int8# uncheckedShiftRLWord8# :: Word8# -> Int# -> Word8# uncheckedShiftLWord8# :: Word8# -> Int# -> Word8# notWord8# :: Word8# -> Word8# xorWord8# :: Word8# -> Word8# -> Word8# orWord8# :: Word8# -> Word8# -> Word8# andWord8# :: Word8# -> Word8# -> Word8# -- | Warning: this can fail with an unchecked exception. quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #) -- | Warning: this can fail with an unchecked exception. remWord8# :: Word8# -> Word8# -> Word8# -- | Warning: this can fail with an unchecked exception. quotWord8# :: Word8# -> Word8# -> Word8# timesWord8# :: Word8# -> Word8# -> Word8# subWord8# :: Word8# -> Word8# -> Word8# plusWord8# :: Word8# -> Word8# -> Word8# wordToWord8# :: Word# -> Word8# word8ToWord# :: Word8# -> Word# neInt8# :: Int8# -> Int8# -> Int# ltInt8# :: Int8# -> Int8# -> Int# leInt8# :: Int8# -> Int8# -> Int# gtInt8# :: Int8# -> Int8# -> Int# geInt8# :: Int8# -> Int8# -> Int# eqInt8# :: Int8# -> Int8# -> Int# int8ToWord8# :: Int8# -> Word8# uncheckedShiftRLInt8# :: Int8# -> Int# -> Int8# uncheckedShiftRAInt8# :: Int8# -> Int# -> Int8# uncheckedShiftLInt8# :: Int8# -> Int# -> Int8# -- | Warning: this can fail with an unchecked exception. quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #) -- | Warning: this can fail with an unchecked exception. remInt8# :: Int8# -> Int8# -> Int8# -- | Warning: this can fail with an unchecked exception. quotInt8# :: Int8# -> Int8# -> Int8# timesInt8# :: Int8# -> Int8# -> Int8# subInt8# :: Int8# -> Int8# -> Int8# plusInt8# :: Int8# -> Int8# -> Int8# negateInt8# :: Int8# -> Int8# intToInt8# :: Int# -> Int8# int8ToInt# :: Int8# -> Int# ord# :: Char# -> Int# leChar# :: Char# -> Char# -> Int# ltChar# :: Char# -> Char# -> Int# neChar# :: Char# -> Char# -> Int# eqChar# :: Char# -> Char# -> Int# geChar# :: Char# -> Char# -> Int# gtChar# :: Char# -> Char# -> Int# rightSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} {s :: RuntimeRep} {n :: Multiplicity} {o :: Multiplicity} (a :: TYPE q) (b :: TYPE r) (c :: TYPE s). (a %n -> b %o -> c) -> b %o -> a %n -> c leftSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} {n :: Multiplicity} (a :: TYPE q) (b :: TYPE r). (a %n -> b) -> a %n -> b -- | Witness for an unboxed Proxy# value, which has no runtime -- representation. proxy# :: forall {k} (a :: k). Proxy# a -- | The value of seq a b is bottom if a is -- bottom, and otherwise equal to b. In other words, it -- evaluates the first argument a to weak head normal form -- (WHNF). 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 :: forall {r :: RuntimeRep} a (b :: TYPE r). a -> b -> b infixr 0 `seq` -- | The null address. nullAddr# :: Addr# -- | This is an alias for the unboxed unit tuple constructor. In earlier -- versions of GHC, void# was a value of the primitive type -- Void#, which is now defined to be (# #). void# :: (# #) -- | The token used in the implementation of the IO monad as a state monad. -- It does not pass any information at runtime. See also runRW#. realWorld# :: State# RealWorld -- | 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# :: forall (r :: RuntimeRep) (o :: TYPE r). (State# RealWorld -> o) -> o -- | 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# -- | Compare the underlying pointers of two values for equality. -- -- Returns 1 if the pointers are equal and 0 otherwise. -- -- The two values must be of the same type, of kind Type. See -- also reallyUnsafePtrEquality#, which doesn't have such -- restrictions. reallyUnsafePtrEquality :: a -> a -> Int# -- | Compare the underlying pointers of two unlifted values for equality. -- -- This is less dangerous than reallyUnsafePtrEquality, since the -- arguments are guaranteed to be evaluated. This means there is no risk -- of accidentally comparing a thunk. It's however still more dangerous -- than e.g. sameArray#. unsafePtrEquality# :: forall (a :: UnliftedType) (b :: UnliftedType). a -> b -> Int# -- | Compare two stable names for equality. eqStableName# :: forall {k :: Levity} {l :: Levity} (a :: TYPE ('BoxedRep k)) (b :: TYPE ('BoxedRep l)). StableName# a -> StableName# b -> Int# -- | Compare the underlying pointers of two arrays. sameArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Array# a -> Int# -- | Compare the underlying pointers of two mutable arrays. sameMutableArray# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). MutableArray# s a -> MutableArray# s a -> Int# -- | Compare the underlying pointers of two small arrays. sameSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> SmallArray# a -> Int# -- | Compare the underlying pointers of two small mutable arrays. sameSmallMutableArray# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). SmallMutableArray# s a -> SmallMutableArray# s a -> Int# -- | Compare the pointers of two byte arrays. sameByteArray# :: ByteArray# -> ByteArray# -> Int# -- | Compare the underlying pointers of two mutable byte arrays. sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int# -- | Compare the underlying pointers of two MVar#s. sameMVar# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). MVar# s a -> MVar# s a -> Int# -- | Compare the underlying pointers of two MutVar#s. sameMutVar# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). MutVar# s a -> MutVar# s a -> Int# -- | Compare the underlying pointers of two TVar#s. sameTVar# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). TVar# s a -> TVar# s a -> Int# -- | Compare the underlying pointers of two IOPort#s. sameIOPort# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). IOPort# s a -> IOPort# s a -> Int# -- | Compare the underlying pointers of two PromptTag#s. samePromptTag# :: PromptTag# a -> PromptTag# a -> Int# -- | An implementation of the old atomicModifyMutVar# primop in -- terms of the new atomicModifyMutVar2# primop, for backwards -- compatibility. The type of this function is a bit bogus. It's best to -- think of it as having type -- --
--   atomicModifyMutVar#
--     :: MutVar# s a
--     -> (a -> (a, b))
--     -> State# s
--     -> (# State# s, b #)
--   
-- -- but there may be code that uses this with other two-field record -- types. atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (# State# s, c #) -- | Resize a mutable array to new specified size. The returned -- SmallMutableArray# is either the original -- SmallMutableArray# resized in-place or, if not possible, a -- newly allocated SmallMutableArray# with the original content -- copied over. -- -- To avoid undefined behaviour, the original SmallMutableArray# -- shall not be accessed anymore after a resizeSmallMutableArray# -- has been performed. Moreover, no reference to the old one should be -- kept in order to allow garbage collection of the original -- SmallMutableArray# in case a new SmallMutableArray# had -- to be allocated. resizeSmallMutableArray# :: SmallMutableArray# s a -> Int# -> a -> State# s -> (# State# s, SmallMutableArray# s a #) -- | A list producer that can be fused with foldr. This function is -- merely -- --
--   build g = g (:) []
--   
-- -- but GHC's simplifier will transform an expression of the form -- foldr k z (build g), which may arise after -- inlining, to g k z, which avoids producing an intermediate -- list. build :: (forall b. () => (a -> b -> b) -> b -> b) -> [a] -- | A list producer that can be fused with foldr. This function is -- merely -- --
--   augment g xs = g (:) xs
--   
-- -- but GHC's simplifier will transform an expression of the form -- foldr k z (augment g xs), which may arise after -- inlining, to g k (foldr k z xs), which avoids -- producing an intermediate list. augment :: (forall b. () => (a -> b -> b) -> b -> b) -> [a] -> [a] -- | The IsList class and its methods are intended to be used in -- conjunction with the OverloadedLists extension. class IsList l where { -- | The Item type function returns the type of items of the -- structure l. type 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 and -- potentially uses it to construct the structure l more -- efficiently compared to fromList. If the given number does not -- equal to the input list's length the behaviour of fromListN is -- not specified. -- --
--   fromListN (length xs) xs == fromList xs
--   
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] -- | 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. -- --
--   >>> compare True False
--   GT
--   
-- --
--   >>> compare (Down True) (Down False)
--   LT
--   
-- -- If a has a Bounded instance then the wrapped -- instance also respects the reversed ordering by exchanging the values -- of minBound and maxBound. -- --
--   >>> minBound :: Int
--   -9223372036854775808
--   
-- --
--   >>> minBound :: Down Int
--   Down 9223372036854775807
--   
-- -- All other instances of Down a behave as they do for -- a. newtype Down a Down :: a -> Down a [getDown] :: Down a -> 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 -- -- In general if the user supplied function is expensive to compute then -- you should probably be using sortOn, as it only needs to -- compute it once for each element. sortWith, on the other hand -- must compute the mapping function for every comparison that it -- performs. 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 -- | IsString is used in combination with the -- -XOverloadedStrings language extension to convert the -- literals to different string types. -- -- For example, if you use the text package, you can say -- --
--   {-# LANGUAGE OverloadedStrings  #-}
--   
--   myText = "hello world" :: Text
--   
-- -- Internally, the extension will convert this to the equivalent of -- --
--   myText = fromString @Text ("hello world" :: String)
--   
-- -- Note: You can use fromString in normal code as well, -- but the usual performance/memory efficiency problems with -- String apply. class IsString a fromString :: IsString a => String -> a unpackCString# :: Addr# -> [Char] unpackAppendCString# :: Addr# -> [Char] -> [Char] unpackFoldrCString# :: Addr# -> (Char -> a -> a) -> a -> a unpackCStringUtf8# :: Addr# -> [Char] unpackNBytes# :: Addr# -> Int# -> [Char] -- | Compute the length of a NUL-terminated string. This address must refer -- to immutable memory. GHC includes a built-in rule for constant folding -- when the argument is a statically-known literal. That is, a -- core-to-core pass reduces the expression cstringLength# -- "hello"# to the constant 5#. cstringLength# :: Addr# -> Int# breakpoint :: a -> a breakpointCond :: Bool -> a -> a -- | Deprecated: Use traceEvent or traceEventIO traceEvent :: String -> IO () -- | 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 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 call noinline f arranges that f will not be -- inlined. It is removed during CorePrep so that its use imposes no -- overhead (besides the fact that it blocks inlining.) noinline :: 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. lazy :: 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 :: forall {q :: RuntimeRep} {r :: RuntimeRep} (a :: TYPE q) (b :: TYPE r). (a -> b) -> a -> b -- | Semantically, considerAccessible = True. But it has special -- meaning to the pattern-match checker, which will never flag the clause -- in which considerAccessible occurs as a guard as redundant or -- inaccessible. Example: -- --
--   case (x, x) of
--     (True,  True)  -> 1
--     (False, False) -> 2
--     (True,  False) -> 3 -- Warning: redundant
--   
-- -- The pattern-match checker will warn here that the third clause is -- redundant. It will stop doing so if the clause is adorned with -- considerAccessible: -- --
--   case (x, x) of
--     (True,  True)  -> 1
--     (False, False) -> 2
--     (True,  False) | considerAccessible -> 3 -- No warning
--   
-- -- Put considerAccessible as the last statement of the guard to -- avoid get confusing results from the pattern-match checker, which -- takes "consider accessible" by word. considerAccessible :: Bool -- | Deprecated, use SPEC directly instead. -- -- Annotating a type with NoSpecConstr will make -- SpecConstr not specialise for arguments of that type, e. g., -- {-# ANN type SPEC ForceSpecConstr #-}. data SpecConstrAnnotation NoSpecConstr :: SpecConstrAnnotation ForceSpecConstr :: SpecConstrAnnotation -- | SPEC is used by GHC in the SpecConstr pass in order to -- inform the compiler when to be particularly aggressive. In particular, -- it tells GHC to specialize regardless of size or the number of -- specializations. However, not all loops fall into this category. -- -- Libraries can specify this by using SPEC data type to inform -- which loops should be aggressively specialized. For example, instead -- of -- --
--   loop x where loop arg = ...
--   
-- -- write -- --
--   loop SPEC x where loop !_ arg = ...
--   
-- -- There is no semantic difference between SPEC and SPEC2, -- we just need a type with two contructors lest it is optimised away -- before SpecConstr. -- -- This type is reexported from GHC.Exts since GHC 9.0 and -- base-4.15. For compatibility with earlier releases import it -- from GHC.Types in ghc-prim package. data SPEC SPEC :: SPEC SPEC2 :: SPEC -- | 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. -- -- When used in conversions involving a newtype wrapper, make sure the -- newtype constructor is in scope. -- -- This function is representation-polymorphic, but the -- RuntimeRep type argument is marked as Inferred, -- meaning that it is not available for visible type application. This -- means the typechecker will accept coerce @Int @Age -- 42. -- --

Examples

-- --
--   >>> newtype TTL = TTL Int deriving (Eq, Ord, Show)
--   
--   >>> newtype Age = Age Int deriving (Eq, Ord, Show)
--   
--   >>> coerce (Age 42) :: TTL
--   TTL 42
--   
--   >>> coerce (+ (1 :: Int)) (Age 42) :: TTL
--   TTL 43
--   
--   >>> coerce (map (+ (1 :: Int))) [Age 42, Age 24] :: [TTL]
--   [TTL 43,TTL 25]
--   
coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b -- | Highly, terribly dangerous coercion from one representation type to -- another. Misuse of this function can invite the garbage collector to -- trounce upon your data and then laugh in your face. You don't want -- this function. Really. unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). a -> b -- | The constraint WithDict cls meth can be solved when -- evidence for the constraint cls can be provided in the form -- of a dictionary of type meth. This requires cls to -- be a class constraint whose single method has type meth. -- -- For more (important) details on how this works, see Note -- [withDict] in GHC.Tc.Instance.Class in GHC. class WithDict cls meth withDict :: forall {rr :: RuntimeRep} (r :: TYPE rr). WithDict cls meth => meth -> (cls => r) -> r maxTupleSize :: Int instance Data.Data.Data GHC.Exts.SpecConstrAnnotation instance GHC.Classes.Eq GHC.Exts.SpecConstrAnnotation -- | This module exposes an interface for capturing the state of a thread's -- execution stack for diagnostics purposes: cloneMyStack, -- cloneThreadStack. -- -- Such a "cloned" stack can be decoded with decode to a stack -- trace, given that the -finfo-table-map is enabled. module GHC.Stack.CloneStack -- | A frozen snapshot of the state of an execution stack. data StackSnapshot StackSnapshot :: !StackSnapshot# -> StackSnapshot -- | Representation for the source location where a return frame was pushed -- on the stack. This happens every time when a case ... of -- scrutinee is evaluated. data StackEntry StackEntry :: String -> String -> String -> Word -> StackEntry [functionName] :: StackEntry -> String [moduleName] :: StackEntry -> String [srcLoc] :: StackEntry -> String [closureType] :: StackEntry -> Word -- | Clone the stack of the executing thread cloneMyStack :: IO StackSnapshot -- | Clone the stack of a thread identified by its ThreadId cloneThreadStack :: ThreadId -> IO StackSnapshot -- | Decode a StackSnapshot to a stacktrace (a list of -- StackEntry). The stack trace is created from return frames with -- according InfoProvEnt entries. To generate them, use the GHC -- flag -finfo-table-map. If there are no InfoProvEnt -- entries, an empty list is returned. -- -- Please note: -- -- decode :: StackSnapshot -> IO [StackEntry] instance GHC.Classes.Eq GHC.Stack.CloneStack.StackEntry instance GHC.Show.Show GHC.Stack.CloneStack.StackEntry -- | Support code for desugaring in GHC module GHC.Desugar (>>>) :: Arrow arr => forall a b c. () => arr a b -> arr b c -> arr a c data AnnotationWrapper AnnotationWrapper :: a -> AnnotationWrapper toAnnotationWrapper :: Data a => a -> AnnotationWrapper -- | A type a is a Semigroup if it provides an associative -- function (<>) that lets you combine any two values of -- type a into one. Where being associative means that the -- following must always hold: -- --
--   (a <> b) <> c == a <> (b <> c)
--   
-- --

Examples

-- -- The Min Semigroup instance for Int is defined to -- always pick the smaller number: -- --
--   >>> Min 1 <> Min 2 <> Min 3 <> Min 4 :: Min Int
--   Min {getMin = 1}
--   
-- -- If we need to combine multiple values we can use the sconcat -- function to do so. We need to ensure however that we have at least one -- value to operate on, since otherwise our result would be undefined. It -- is for this reason that sconcat uses -- Data.List.NonEmpty.NonEmpty - a list that can never be empty: -- --
--   >>> (1 :| [])
--   1 :| []               -- equivalent to [1] but guaranteed to be non-empty.
--   
-- --
--   >>> (1 :| [2, 3, 4])
--   1 :| [2,3,4]          -- equivalent to [1,2,3,4] but guaranteed to be non-empty.
--   
-- -- Equipped with this guaranteed to be non-empty data structure, we can -- combine values using sconcat and a Semigroup of our -- choosing. We can try the Min and Max instances of -- Int which pick the smallest, or largest number respectively: -- --
--   >>> sconcat (1 :| [2, 3, 4]) :: Min Int
--   Min {getMin = 1}
--   
-- --
--   >>> sconcat (1 :| [2, 3, 4]) :: Max Int
--   Max {getMax = 4}
--   
-- -- String concatenation is another example of a Semigroup -- instance: -- --
--   >>> "foo" <> "bar"
--   "foobar"
--   
-- -- A Semigroup is a generalization of a Monoid. Yet unlike -- the Semigroup, the Monoid requires the presence of a -- neutral element (mempty) in addition to the associative -- operator. The requirement for a neutral element prevents many types -- from being a full Monoid, like Data.List.NonEmpty.NonEmpty. -- -- Note that 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). -- -- Instances should satisfy the following: -- -- -- -- You can alternatively define sconcat instead of -- (<>), in which case the laws are: -- -- class Semigroup a -- | An associative operation. -- --

Examples

-- --
--   >>> [1,2,3] <> [4,5,6]
--   [1,2,3,4,5,6]
--   
-- --
--   >>> Just [1, 2, 3] <> Just [4, 5, 6]
--   Just [1,2,3,4,5,6]
--   
-- --
--   >>> putStr "Hello, " <> putStrLn "World!"
--   Hello, World!
--   
(<>) :: Semigroup a => a -> a -> a -- | Reduce a non-empty list with <> -- -- The default definition should be sufficient, but this can be -- overridden for efficiency. -- --

Examples

-- -- For the following examples, we will assume that we have: -- --
--   >>> import Data.List.NonEmpty (NonEmpty (..))
--   
-- --
--   >>> sconcat $ "Hello" :| [" ", "Haskell", "!"]
--   "Hello Haskell!"
--   
-- --
--   >>> sconcat $ Just [1, 2, 3] :| [Nothing, Just [4, 5, 6]]
--   Just [1,2,3,4,5,6]
--   
-- --
--   >>> sconcat $ Left 1 :| [Right 2, Left 3, Right 4]
--   Right 2
--   
sconcat :: Semigroup a => NonEmpty a -> a -- | Repeat a value n times. -- -- The default definition will raise an exception for a multiplier that -- is <= 0. This may be overridden with an implementation -- that is total. For monoids it is preferred to use -- stimesMonoid. -- -- By making this a member of the class, idempotent semigroups and -- monoids can upgrade this to execute in <math> by picking -- stimes = stimesIdempotent or stimes = -- stimesIdempotentMonoid respectively. -- --

Examples

-- --
--   >>> stimes 4 [1]
--   [1,1,1,1]
--   
-- --
--   >>> stimes 5 (putStr "hi!")
--   hi!hi!hi!hi!hi!
--   
-- --
--   >>> stimes 3 (Right ":)")
--   Right ":)"
--   
stimes :: (Semigroup a, Integral b) => b -> a -> a infixr 6 <> -- | 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 <math> rather than <math>. stimesIdempotent :: Integral b => b -> a -> a -- | This is a valid definition of stimes for an idempotent -- Monoid. -- -- When x <> x = x, this definition should be preferred, -- because it works in <math> rather than <math> stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a -- | Repeat a value n times. -- --
--   mtimesDefault n a = a <> a <> ... <> a  -- using <> (n-1) times
--   
-- -- In many cases, stimes 0 a for a Monoid will -- produce mempty. However, there are situations when it cannot do -- so. In particular, the following situation is fairly common: -- --
--   data T a = ...
--   
--   class Constraint1 a
--   class Constraint1 a => Constraint2 a
--   
-- --
--   instance Constraint1 a => Semigroup (T a)
--   instance Constraint2 a => Monoid (T a)
--   
-- -- Since Constraint1 is insufficient to implement mempty, -- stimes for T a cannot do so. -- -- When working with such a type, or when working polymorphically with -- Semigroup instances, mtimesDefault should be used when -- the multiplier might be zero. It is implemented using stimes -- when the multiplier is nonzero and mempty when it is zero. -- --

Examples

-- --
--   >>> mtimesDefault 0 "bark"
--   []
--   
-- --
--   >>> mtimesDefault 3 "meow"
--   "meowmeowmeow"
--   
mtimesDefault :: (Integral b, Monoid a) => b -> a -> a -- | The Min Monoid and Semigroup always choose the -- smaller element as by the Ord instance and min of the -- contained type. -- --

Examples

-- --
--   >>> Min 42 <> Min 3
--   Min 3
--   
-- --
--   >>> sconcat $ Min 1 :| [ Min n | n <- [2 .. 100]]
--   Min {getMin = 1}
--   
newtype Min a Min :: a -> Min a [getMin] :: Min a -> a -- | The Max Monoid and Semigroup always choose the -- bigger element as by the Ord instance and max of the -- contained type. -- --

Examples

-- --
--   >>> Max 42 <> Max 3
--   Max 42
--   
-- --
--   >>> sconcat $ Max 1 :| [ Max n | n <- [2 .. 100]]
--   Max {getMax = 100}
--   
newtype Max a Max :: a -> Max a [getMax] :: Max a -> a -- | Beware that Data.Semigroup.First is different from -- Data.Monoid.First. The former simply returns the first -- value, so Data.Semigroup.First Nothing <> x = -- Data.Semigroup.First Nothing. The latter returns the first -- non-Nothing, thus Data.Monoid.First Nothing <> x = -- x. -- --

Examples

-- --
--   >>> First 0 <> First 10
--   First 0
--   
-- --
--   >>> sconcat $ First 1 :| [ First n | n <- [2 ..] ]
--   First 1
--   
newtype First a First :: a -> First a [getFirst] :: First a -> a -- | Beware that Data.Semigroup.Last is different from -- Data.Monoid.Last. The former simply returns the last -- value, so x <> Data.Semigroup.Last Nothing = -- Data.Semigroup.Last Nothing. The latter returns the last -- non-Nothing, thus x <> Data.Monoid.Last Nothing = -- x. -- --

Examples

-- --
--   >>> Last 0 <> Last 10
--   Last {getLast = 10}
--   
-- --
--   >>> sconcat $ Last 1 :| [ Last n | n <- [2..]]
--   Last {getLast = * hangs forever *
--   
newtype Last a Last :: a -> Last a [getLast] :: Last a -> a -- | Provide a Semigroup for an arbitrary Monoid. -- -- NOTE: This is not needed anymore since Semigroup became -- a superclass of Monoid in base-4.11 and this newtype be -- deprecated at some point in the future. newtype WrappedMonoid m WrapMonoid :: m -> WrappedMonoid m [unwrapMonoid] :: WrappedMonoid m -> m -- | The dual of a Monoid, obtained by swapping the arguments of -- (<>). -- --
--   Dual a <> Dual b == Dual (b <> a)
--   
-- --

Examples

-- --
--   >>> Dual "Hello" <> Dual "World"
--   Dual {getDual = "WorldHello"}
--   
-- --
--   >>> Dual (Dual "Hello") <> Dual (Dual "World")
--   Dual {getDual = Dual {getDual = "HelloWorld"}}
--   
newtype Dual a Dual :: a -> Dual a [getDual] :: Dual a -> a -- | The monoid of endomorphisms under composition. -- --
--   Endo f <> Endo g == Endo (f . g)
--   
-- --

Examples

-- --
--   >>> let computation = Endo ("Hello, " ++) <> Endo (++ "!")
--   
--   >>> appEndo computation "Haskell"
--   "Hello, Haskell!"
--   
-- --
--   >>> let computation = Endo (*3) <> Endo (+1)
--   
--   >>> appEndo computation 1
--   6
--   
newtype Endo a Endo :: (a -> a) -> Endo a [appEndo] :: Endo a -> a -> a -- | Boolean monoid under conjunction (&&). -- --
--   All x <> All y = All (x && y)
--   
-- --

Examples

-- --
--   >>> All True <> mempty <> All False)
--   All {getAll = False}
--   
-- --
--   >>> mconcat (map (\x -> All (even x)) [2,4,6,7,8])
--   All {getAll = False}
--   
-- --
--   >>> All True <> mempty
--   All {getAll = True}
--   
newtype All All :: Bool -> All [getAll] :: All -> Bool -- | Boolean monoid under disjunction (||). -- --
--   Any x <> Any y = Any (x || y)
--   
-- --

Examples

-- --
--   >>> Any True <> mempty <> Any False
--   Any {getAny = True}
--   
-- --
--   >>> mconcat (map (\x -> Any (even x)) [2,4,6,7,8])
--   Any {getAny = True}
--   
-- --
--   >>> Any False <> mempty
--   Any {getAny = False}
--   
newtype Any Any :: Bool -> Any [getAny] :: Any -> Bool -- | Monoid under addition. -- --
--   Sum a <> Sum b = Sum (a + b)
--   
-- --

Examples

-- --
--   >>> Sum 1 <> Sum 2 <> mempty
--   Sum {getSum = 3}
--   
-- --
--   >>> mconcat [ Sum n | n <- [3 .. 9]]
--   Sum {getSum = 42}
--   
newtype Sum a Sum :: a -> Sum a [getSum] :: Sum a -> a -- | Monoid under multiplication. -- --
--   Product x <> Product y == Product (x * y)
--   
-- --

Examples

-- --
--   >>> Product 3 <> Product 4 <> mempty
--   Product {getProduct = 12}
--   
-- --
--   >>> mconcat [ Product n | n <- [2 .. 10]]
--   Product {getProduct = 3628800}
--   
newtype Product a Product :: a -> Product a [getProduct] :: Product a -> a -- | This lets you use a difference list of a Semigroup as a -- Monoid. -- --

Examples

-- --
--   let hello = diff "Hello, "
--   
-- --
--   >>> appEndo hello "World!"
--   "Hello, World!"
--   
-- --
--   >>> appEndo (hello <> mempty) "World!"
--   "Hello, World!"
--   
-- --
--   >>> appEndo (mempty <> hello) "World!"
--   "Hello, World!"
--   
-- --
--   let world = diff "World"
--   let excl = diff "!"
--   
-- --
--   >>> appEndo (hello <> (world <> excl)) mempty
--   "Hello, World!"
--   
-- --
--   >>> appEndo ((hello <> world) <> excl) mempty
--   "Hello, World!"
--   
diff :: Semigroup m => m -> Endo m -- | A generalization of cycle to an arbitrary Semigroup. May -- fail to terminate for some values in some semigroups. -- --

Examples

-- --
--   >>> take 10 $ cycle1 [1, 2, 3]
--   [1,2,3,1,2,3,1,2,3,1]
--   
-- --
--   >>> cycle1 (Right 1)
--   Right 1
--   
-- --
--   >>> cycle1 (Left 1)
--   * hangs forever *
--   
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. -- --

Examples

-- --
--   >>> minimum [ Arg (x * x) x | x <- [-10 .. 10] ]
--   Arg 0 0
--   
-- --
--   >>> maximum [ Arg (-0.2*x^2 + 1.5*x + 1) x | x <- [-10 .. 10] ]
--   Arg 3.8 4.0
--   
-- --
--   >>> minimum [ Arg (-0.2*x^2 + 1.5*x + 1) x | x <- [-10 .. 10] ]
--   Arg (-34.0) (-10.0)
--   
data Arg a b Arg :: a -> b -> Arg a b -- |

Examples

-- --
--   >>> Min (Arg 0 ()) <> Min (Arg 1 ())
--   Min {getMin = Arg 0 ()}
--   
-- --
--   >>> minimum [ Arg (length name) name | name <- ["violencia", "lea", "pixie"]]
--   Arg 3 "lea"
--   
type ArgMin a b = Min Arg a b -- |

Examples

-- --
--   >>> Max (Arg 0 ()) <> Max (Arg 1 ())
--   Max {getMax = Arg 1 ()}
--   
-- --
--   >>> maximum [ Arg (length name) name | name <- ["violencia", "lea", "pixie"]]
--   Arg 9 "violencia"
--   
type ArgMax a b = Max Arg a b instance GHC.Base.Applicative Data.Semigroup.First instance GHC.Base.Applicative Data.Semigroup.Last instance GHC.Base.Applicative Data.Semigroup.Max instance GHC.Base.Applicative Data.Semigroup.Min instance Data.Bifoldable.Bifoldable Data.Semigroup.Arg instance Data.Bifunctor.Bifunctor Data.Semigroup.Arg instance Data.Bitraversable.Bitraversable Data.Semigroup.Arg instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.First a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.Last a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.Max a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.Min a) instance GHC.Enum.Bounded m => GHC.Enum.Bounded (Data.Semigroup.WrappedMonoid m) instance (Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Data.Semigroup.Arg a b) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.First a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Last a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Max a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Min a) instance Data.Data.Data m => Data.Data.Data (Data.Semigroup.WrappedMonoid m) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.First a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.Last a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.Max a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.Min a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.WrappedMonoid a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Arg a b) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.First a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Last a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Max a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Min a) instance GHC.Classes.Eq m => GHC.Classes.Eq (Data.Semigroup.WrappedMonoid m) instance Data.Foldable.Foldable (Data.Semigroup.Arg a) instance Data.Foldable.Foldable Data.Semigroup.First instance Data.Foldable.Foldable Data.Semigroup.Last instance Data.Foldable.Foldable Data.Semigroup.Max instance Data.Foldable.Foldable Data.Semigroup.Min instance GHC.Base.Functor (Data.Semigroup.Arg a) instance GHC.Base.Functor Data.Semigroup.First instance GHC.Base.Functor Data.Semigroup.Last instance GHC.Base.Functor Data.Semigroup.Max instance GHC.Base.Functor Data.Semigroup.Min instance GHC.Generics.Generic1 (Data.Semigroup.Arg a) instance GHC.Generics.Generic1 Data.Semigroup.First instance GHC.Generics.Generic1 Data.Semigroup.Last instance GHC.Generics.Generic1 Data.Semigroup.Max instance GHC.Generics.Generic1 Data.Semigroup.Min instance GHC.Generics.Generic1 Data.Semigroup.WrappedMonoid instance GHC.Generics.Generic (Data.Semigroup.Arg a b) instance GHC.Generics.Generic (Data.Semigroup.First a) instance GHC.Generics.Generic (Data.Semigroup.Last a) instance GHC.Generics.Generic (Data.Semigroup.Max a) instance GHC.Generics.Generic (Data.Semigroup.Min a) instance GHC.Generics.Generic (Data.Semigroup.WrappedMonoid m) instance Control.Monad.Fix.MonadFix Data.Semigroup.First instance Control.Monad.Fix.MonadFix Data.Semigroup.Last instance Control.Monad.Fix.MonadFix Data.Semigroup.Max instance Control.Monad.Fix.MonadFix Data.Semigroup.Min instance GHC.Base.Monad Data.Semigroup.First instance GHC.Base.Monad Data.Semigroup.Last instance GHC.Base.Monad Data.Semigroup.Max instance GHC.Base.Monad Data.Semigroup.Min instance (GHC.Classes.Ord a, GHC.Enum.Bounded a) => GHC.Base.Monoid (Data.Semigroup.Max a) instance (GHC.Classes.Ord a, GHC.Enum.Bounded a) => GHC.Base.Monoid (Data.Semigroup.Min a) instance GHC.Base.Monoid m => GHC.Base.Monoid (Data.Semigroup.WrappedMonoid m) instance GHC.Num.Num a => GHC.Num.Num (Data.Semigroup.Max a) instance GHC.Num.Num a => GHC.Num.Num (Data.Semigroup.Min a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Arg a b) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.First a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Last a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Max a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Min a) instance GHC.Classes.Ord m => GHC.Classes.Ord (Data.Semigroup.WrappedMonoid m) instance (GHC.Read.Read a, GHC.Read.Read b) => GHC.Read.Read (Data.Semigroup.Arg a b) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.First a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Last a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Max a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Min a) instance GHC.Read.Read m => GHC.Read.Read (Data.Semigroup.WrappedMonoid m) instance GHC.Base.Semigroup (Data.Semigroup.First a) instance GHC.Base.Semigroup (Data.Semigroup.Last a) instance GHC.Classes.Ord a => GHC.Base.Semigroup (Data.Semigroup.Max a) instance GHC.Classes.Ord a => GHC.Base.Semigroup (Data.Semigroup.Min a) instance GHC.Base.Monoid m => GHC.Base.Semigroup (Data.Semigroup.WrappedMonoid m) instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Data.Semigroup.Arg a b) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.First a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Last a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Max a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Min a) instance GHC.Show.Show m => GHC.Show.Show (Data.Semigroup.WrappedMonoid m) instance Data.Traversable.Traversable (Data.Semigroup.Arg a) instance Data.Traversable.Traversable Data.Semigroup.First instance Data.Traversable.Traversable Data.Semigroup.Last instance Data.Traversable.Traversable Data.Semigroup.Max instance Data.Traversable.Traversable Data.Semigroup.Min module Data.Bifoldable1 class Bifoldable t => Bifoldable1 (t :: Type -> Type -> Type) bifold1 :: (Bifoldable1 t, Semigroup m) => t m m -> m bifoldMap1 :: (Bifoldable1 t, Semigroup m) => (a -> m) -> (b -> m) -> t a b -> m instance Data.Bifoldable1.Bifoldable1 Data.Semigroup.Arg instance Data.Bifoldable1.Bifoldable1 Data.Functor.Const.Const instance Data.Bifoldable1.Bifoldable1 Data.Either.Either instance Data.Bifoldable1.Bifoldable1 (,) instance Data.Bifoldable1.Bifoldable1 ((,,) x) instance Data.Bifoldable1.Bifoldable1 ((,,,) x y) instance Data.Bifoldable1.Bifoldable1 ((,,,,) x y z) -- | 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. -- -- Automatic conversion between different Fixed can be performed -- through realToFrac, bear in mind that converting to a fixed -- with a smaller resolution will truncate the number, losing -- information. -- --
--   >>> realToFrac (0.123456 :: Pico) :: Milli
--   0.123
--   
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 :: k) MkFixed :: Integer -> Fixed (a :: k) class HasResolution (a :: k) resolution :: HasResolution a => p a -> Integer -- | First arg is whether to chop off trailing zeros showFixed :: forall {k} (a :: k). 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 forall k (a :: k). (Data.Typeable.Internal.Typeable k, Data.Typeable.Internal.Typeable a) => Data.Data.Data (Data.Fixed.Fixed a) instance forall k (a :: k). GHC.Enum.Enum (Data.Fixed.Fixed a) instance forall k (a :: k). GHC.Classes.Eq (Data.Fixed.Fixed a) instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.Fractional (Data.Fixed.Fixed a) instance GHC.TypeNats.KnownNat n => Data.Fixed.HasResolution n instance Data.Fixed.HasResolution Data.Fixed.E0 instance Data.Fixed.HasResolution Data.Fixed.E1 instance Data.Fixed.HasResolution Data.Fixed.E12 instance Data.Fixed.HasResolution Data.Fixed.E2 instance Data.Fixed.HasResolution Data.Fixed.E3 instance Data.Fixed.HasResolution Data.Fixed.E6 instance Data.Fixed.HasResolution Data.Fixed.E9 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Num.Num (Data.Fixed.Fixed a) instance forall k (a :: k). GHC.Classes.Ord (Data.Fixed.Fixed a) instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Read.Read (Data.Fixed.Fixed a) instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.Real (Data.Fixed.Fixed a) instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Real.RealFrac (Data.Fixed.Fixed a) instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Show.Show (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. -- -- Note that Complex's instances inherit the deficiencies from the -- type parameter's. For example, Complex Float's Ord -- instance has similar problems to Float's. data Complex a -- | forms a complex number from its real and imaginary rectangular -- components. (:+) :: !a -> !a -> Complex a infix 6 :+ -- | 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 -- non-negative, 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 non-negative 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 GHC.Base.Applicative Data.Complex.Complex instance Data.Data.Data a => Data.Data.Data (Data.Complex.Complex a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Complex.Complex a) instance GHC.Float.RealFloat a => GHC.Float.Floating (Data.Complex.Complex a) instance Data.Foldable.Foldable Data.Complex.Complex instance GHC.Float.RealFloat a => GHC.Real.Fractional (Data.Complex.Complex a) instance GHC.Base.Functor Data.Complex.Complex instance GHC.Generics.Generic1 Data.Complex.Complex instance GHC.Generics.Generic (Data.Complex.Complex a) instance GHC.Base.Monad Data.Complex.Complex instance Control.Monad.Fix.MonadFix Data.Complex.Complex instance Control.Monad.Zip.MonadZip Data.Complex.Complex instance GHC.Float.RealFloat a => GHC.Num.Num (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 Foreign.Storable.Storable a => Foreign.Storable.Storable (Data.Complex.Complex a) instance Data.Traversable.Traversable Data.Complex.Complex -- | 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. -- -- Any instance should be subject to the following law that canonicity is -- preserved: -- -- liftEq (==) = (==) -- -- This class therefore represents the generalization of Eq by -- decomposing its main method into a canonical lifting on a canonical -- inner method, so that the lifting can be reused for other arguments -- than the canonical one. class forall a. Eq a => Eq f a => Eq1 (f :: Type -> Type) -- | 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 ($dmliftEq) :: forall (f' :: Type -> Type -> Type) c a b. (Eq1 f, f ~ f' c, Eq2 f', Eq c) => (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. -- -- Any instance should be subject to the following law that canonicity is -- preserved: -- -- liftCompare compare = compare -- -- This class therefore represents the generalization of Ord by -- decomposing its main method into a canonical lifting on a canonical -- inner method, so that the lifting can be reused for other arguments -- than the canonical one. class (Eq1 f, forall a. Ord a => Ord f a) => Ord1 (f :: Type -> Type) -- | 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 ($dmliftCompare) :: forall (f' :: Type -> Type -> Type) c a b. (Ord1 f, f ~ f' c, Ord2 f', Ord c) => (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. -- -- Any instance should be subject to the following laws that canonicity -- is preserved: -- -- liftReadsPrec readsPrec readList = readsPrec -- -- liftReadList readsPrec readList = readList -- -- liftReadPrec readPrec readListPrec = readPrec -- -- liftReadListPrec readPrec readListPrec = readListPrec -- -- This class therefore represents the generalization of Read by -- decomposing it's methods into a canonical lifting on a canonical inner -- method, so that the lifting can be reused for other arguments than the -- canonical one. -- -- 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 forall a. Read a => Read f a => Read1 (f :: Type -> Type) -- | 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. -- -- Any instance should be subject to the following laws that canonicity -- is preserved: -- -- liftShowsPrec showsPrec showList = showsPrec -- -- liftShowList showsPrec showList = showList -- -- This class therefore represents the generalization of Show by -- decomposing it's methods into a canonical lifting on a canonical inner -- method, so that the lifting can be reused for other arguments than the -- canonical one. class forall a. Show a => Show f a => Show1 (f :: Type -> Type) -- | 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 ($dmliftShowsPrec) :: forall (f' :: Type -> Type -> Type) b a. (Show1 f, f ~ f' b, Show2 f', Show b) => (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 forall a. Eq a => Eq1 f a => Eq2 (f :: Type -> Type -> Type) -- | 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, forall a. Ord a => Ord1 f a) => Ord2 (f :: Type -> Type -> Type) -- | 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. class forall a. Read a => Read1 f a => Read2 (f :: Type -> Type -> Type) -- | 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 forall a. Show a => Show1 f a => Show2 (f :: Type -> Type -> Type) -- | 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.Eq1 Data.Complex.Complex instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Eq1 Data.Ord.Down instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 (Data.Either.Either a) instance (GHC.Generics.Generic1 f, Data.Functor.Classes.Eq1 (GHC.Generics.Rep1 f)) => Data.Functor.Classes.Eq1 (GHC.Generics.Generically1 f) instance Data.Functor.Classes.Eq1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Eq1 [] instance Data.Functor.Classes.Eq1 GHC.Maybe.Maybe instance Data.Functor.Classes.Eq1 GHC.Base.NonEmpty instance Data.Functor.Classes.Eq1 Data.Proxy.Proxy instance Data.Functor.Classes.Eq1 GHC.Tuple.Prim.Solo instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 ((,) a) instance (GHC.Classes.Eq a, GHC.Classes.Eq b) => Data.Functor.Classes.Eq1 ((,,) a b) instance (GHC.Classes.Eq a, GHC.Classes.Eq b, GHC.Classes.Eq c) => Data.Functor.Classes.Eq1 ((,,,) a b c) instance Data.Functor.Classes.Eq2 Data.Functor.Const.Const instance Data.Functor.Classes.Eq2 Data.Either.Either instance Data.Functor.Classes.Eq2 (,) instance GHC.Classes.Eq a => Data.Functor.Classes.Eq2 ((,,) a) instance (GHC.Classes.Eq a, GHC.Classes.Eq b) => Data.Functor.Classes.Eq2 ((,,,) a b) instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Ord1 Data.Ord.Down instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 (Data.Either.Either a) instance (GHC.Generics.Generic1 f, Data.Functor.Classes.Ord1 (GHC.Generics.Rep1 f)) => Data.Functor.Classes.Ord1 (GHC.Generics.Generically1 f) instance Data.Functor.Classes.Ord1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Ord1 [] instance Data.Functor.Classes.Ord1 GHC.Maybe.Maybe instance Data.Functor.Classes.Ord1 GHC.Base.NonEmpty instance Data.Functor.Classes.Ord1 Data.Proxy.Proxy instance Data.Functor.Classes.Ord1 GHC.Tuple.Prim.Solo instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 ((,) a) instance (GHC.Classes.Ord a, GHC.Classes.Ord b) => Data.Functor.Classes.Ord1 ((,,) a b) instance (GHC.Classes.Ord a, GHC.Classes.Ord b, GHC.Classes.Ord c) => Data.Functor.Classes.Ord1 ((,,,) a b c) instance Data.Functor.Classes.Ord2 Data.Functor.Const.Const instance Data.Functor.Classes.Ord2 Data.Either.Either instance Data.Functor.Classes.Ord2 (,) instance GHC.Classes.Ord a => Data.Functor.Classes.Ord2 ((,,) a) instance (GHC.Classes.Ord a, GHC.Classes.Ord b) => Data.Functor.Classes.Ord2 ((,,,) a b) instance Data.Functor.Classes.Read1 Data.Complex.Complex instance GHC.Read.Read a => Data.Functor.Classes.Read1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Read1 Data.Ord.Down instance GHC.Read.Read a => Data.Functor.Classes.Read1 (Data.Either.Either a) instance Data.Functor.Classes.Read1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Read1 [] instance Data.Functor.Classes.Read1 GHC.Maybe.Maybe instance Data.Functor.Classes.Read1 GHC.Base.NonEmpty instance Data.Functor.Classes.Read1 Data.Proxy.Proxy instance Data.Functor.Classes.Read1 GHC.Tuple.Prim.Solo instance GHC.Read.Read a => Data.Functor.Classes.Read1 ((,) a) instance (GHC.Read.Read a, GHC.Read.Read b) => Data.Functor.Classes.Read1 ((,,) a b) instance (GHC.Read.Read a, GHC.Read.Read b, GHC.Read.Read c) => Data.Functor.Classes.Read1 ((,,,) a b c) instance Data.Functor.Classes.Read2 Data.Functor.Const.Const instance Data.Functor.Classes.Read2 Data.Either.Either instance Data.Functor.Classes.Read2 (,) instance GHC.Read.Read a => Data.Functor.Classes.Read2 ((,,) a) instance (GHC.Read.Read a, GHC.Read.Read b) => Data.Functor.Classes.Read2 ((,,,) a b) instance Data.Functor.Classes.Show1 Data.Complex.Complex instance GHC.Show.Show a => Data.Functor.Classes.Show1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Show1 Data.Ord.Down instance GHC.Show.Show a => Data.Functor.Classes.Show1 (Data.Either.Either a) instance Data.Functor.Classes.Show1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Show1 [] instance Data.Functor.Classes.Show1 GHC.Maybe.Maybe instance Data.Functor.Classes.Show1 GHC.Base.NonEmpty instance Data.Functor.Classes.Show1 Data.Proxy.Proxy instance Data.Functor.Classes.Show1 GHC.Tuple.Prim.Solo instance GHC.Show.Show a => Data.Functor.Classes.Show1 ((,) a) instance (GHC.Show.Show a, GHC.Show.Show b) => Data.Functor.Classes.Show1 ((,,) a b) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c) => Data.Functor.Classes.Show1 ((,,,) a b c) instance Data.Functor.Classes.Show2 Data.Functor.Const.Const instance Data.Functor.Classes.Show2 Data.Either.Either instance Data.Functor.Classes.Show2 (,) instance GHC.Show.Show a => Data.Functor.Classes.Show2 ((,,) a) instance (GHC.Show.Show a, GHC.Show.Show b) => Data.Functor.Classes.Show2 ((,,,) a b) -- | Sums, lifted to functors. module Data.Functor.Sum -- | Lifted sum of functors. data Sum (f :: k -> Type) (g :: k -> Type) (a :: k) InL :: f a -> Sum (f :: k -> Type) (g :: k -> Type) (a :: k) InR :: g a -> Sum (f :: k -> Type) (g :: k -> Type) (a :: k) instance forall k (f :: k -> *) (g :: k -> *) (a :: k). (Data.Typeable.Internal.Typeable a, Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable g, Data.Typeable.Internal.Typeable k, Data.Data.Data (f a), Data.Data.Data (g 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 forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Classes.Eq (f a), GHC.Classes.Eq (g a)) => GHC.Classes.Eq (Data.Functor.Sum.Sum f g a) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (Data.Functor.Sum.Sum f g) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (Data.Functor.Sum.Sum f g) 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 (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g) => Data.Functor.Classes.Ord1 (Data.Functor.Sum.Sum f g) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Classes.Ord (f a), GHC.Classes.Ord (g a)) => GHC.Classes.Ord (Data.Functor.Sum.Sum f g a) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g) => Data.Functor.Classes.Read1 (Data.Functor.Sum.Sum f g) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Read.Read (f a), GHC.Read.Read (g a)) => GHC.Read.Read (Data.Functor.Sum.Sum f g a) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g) => Data.Functor.Classes.Show1 (Data.Functor.Sum.Sum f g) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Show.Show (f a), GHC.Show.Show (g a)) => GHC.Show.Show (Data.Functor.Sum.Sum f g a) 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 :: k -> Type) (g :: k -> Type) (a :: k) Pair :: f a -> g a -> Product (f :: k -> Type) (g :: k -> Type) (a :: k) instance (GHC.Base.Alternative f, GHC.Base.Alternative g) => GHC.Base.Alternative (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 forall k (f :: k -> *) (g :: k -> *) (a :: k). (Data.Typeable.Internal.Typeable a, Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable g, Data.Typeable.Internal.Typeable k, Data.Data.Data (f a), Data.Data.Data (g 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 forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Classes.Eq (f a), GHC.Classes.Eq (g a)) => GHC.Classes.Eq (Data.Functor.Product.Product f g a) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (Data.Functor.Product.Product f g) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (Data.Functor.Product.Product f g) 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 (Control.Monad.Fix.MonadFix f, Control.Monad.Fix.MonadFix g) => Control.Monad.Fix.MonadFix (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 (GHC.Base.Monad f, GHC.Base.Monad g) => GHC.Base.Monad (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) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Base.Monoid (f a), GHC.Base.Monoid (g a)) => GHC.Base.Monoid (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g) => Data.Functor.Classes.Ord1 (Data.Functor.Product.Product f g) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Classes.Ord (f a), GHC.Classes.Ord (g a)) => GHC.Classes.Ord (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g) => Data.Functor.Classes.Read1 (Data.Functor.Product.Product f g) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Read.Read (f a), GHC.Read.Read (g a)) => GHC.Read.Read (Data.Functor.Product.Product f g a) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Base.Semigroup (f a), GHC.Base.Semigroup (g a)) => GHC.Base.Semigroup (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g) => Data.Functor.Classes.Show1 (Data.Functor.Product.Product f g) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (GHC.Show.Show (f a), GHC.Show.Show (g a)) => GHC.Show.Show (Data.Functor.Product.Product f g a) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (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 :: k -> Type) (g :: k1 -> k) (a :: k1) Compose :: f (g a) -> Compose (f :: k -> Type) (g :: k1 -> k) (a :: k1) [getCompose] :: Compose (f :: k -> Type) (g :: k1 -> k) (a :: k1) -> f (g a) infixr 9 `Compose` infixr 9 `Compose` instance (GHC.Base.Alternative f, GHC.Base.Applicative g) => GHC.Base.Alternative (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 forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Bounded (f (g a)) => GHC.Enum.Bounded (Data.Functor.Compose.Compose f g a) instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). (Data.Typeable.Internal.Typeable a, Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable g, Data.Typeable.Internal.Typeable k1, Data.Typeable.Internal.Typeable k2, Data.Data.Data (f (g a))) => Data.Data.Data (Data.Functor.Compose.Compose f g a) instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Enum (f (g a)) => GHC.Enum.Enum (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 forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Classes.Eq (f (g a)) => GHC.Classes.Eq (Data.Functor.Compose.Compose f g a) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (Data.Functor.Compose.Compose f g) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (Data.Functor.Compose.Compose f g) 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 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.Integral (f (g a)) => GHC.Real.Integral (Data.Functor.Compose.Compose f g a) instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). GHC.Base.Monoid (f (g a)) => GHC.Base.Monoid (Data.Functor.Compose.Compose f g a) instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Num.Num (f (g a)) => GHC.Num.Num (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g) => Data.Functor.Classes.Ord1 (Data.Functor.Compose.Compose f g) instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Classes.Ord (f (g a)) => GHC.Classes.Ord (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g) => Data.Functor.Classes.Read1 (Data.Functor.Compose.Compose f g) instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Read.Read (f (g a)) => GHC.Read.Read (Data.Functor.Compose.Compose f g a) instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Real.Real (f (g a)) => GHC.Real.Real (Data.Functor.Compose.Compose f g a) instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). GHC.Base.Semigroup (f (g a)) => GHC.Base.Semigroup (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g) => Data.Functor.Classes.Show1 (Data.Functor.Compose.Compose f g) instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Show.Show (f (g a)) => GHC.Show.Show (Data.Functor.Compose.Compose f g a) instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1). Data.Type.Equality.TestEquality f => Data.Type.Equality.TestEquality (Data.Functor.Compose.Compose f g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (Data.Functor.Compose.Compose f g) -- | Contravariant functors, sometimes referred to colloquially as -- Cofunctor, even though the dual of a Functor is just a -- Functor. As with Functor the definition of -- Contravariant for a given ADT is unambiguous. module Data.Functor.Contravariant -- | The class of contravariant functors. -- -- Whereas in Haskell, one can think of a Functor as containing or -- producing values, a contravariant functor is a functor that can be -- thought of as consuming values. -- -- As an example, consider the type of predicate functions a -> -- Bool. One such predicate might be negative x = x < 0, -- which classifies integers as to whether they are negative. However, -- given this predicate, we can re-use it in other situations, providing -- we have a way to map values to integers. For instance, we can -- use the negative predicate on a person's bank balance to work -- out if they are currently overdrawn: -- --
--   newtype Predicate a = Predicate { getPredicate :: a -> Bool }
--   
--   instance Contravariant Predicate where
--     contramap :: (a' -> a) -> (Predicate a -> Predicate a')
--     contramap f (Predicate p) = Predicate (p . f)
--                                            |   `- First, map the input...
--                                            `----- then apply the predicate.
--   
--   overdrawn :: Predicate Person
--   overdrawn = contramap personBankBalance negative
--   
-- -- Any instance should be subject to the following laws: -- -- -- -- Note, that the second law follows from the free theorem of the type of -- contramap and the first law, so you need only check that the -- former condition holds. class Contravariant (f :: Type -> Type) contramap :: Contravariant f => (a' -> a) -> f a -> f a' -- | Replace all locations in the output with the same value. The default -- definition is contramap . const, but this may -- be overridden with a more efficient version. (>$) :: Contravariant f => b -> f b -> f a infixl 4 >$ -- | If f is both Functor and Contravariant then by -- the time you factor in the laws of each of those classes, it can't -- actually use its argument in any meaningful capacity. -- -- This method is surprisingly useful. Where both instances exist and are -- lawful we have the following laws: -- --
--   fmap      f ≡ phantom
--   contramap f ≡ phantom
--   
phantom :: (Functor f, Contravariant f) => f a -> f b -- | This is an infix alias for contramap. (>$<) :: Contravariant f => (a -> b) -> f b -> f a infixl 4 >$< -- | This is an infix version of contramap with the arguments -- flipped. (>$$<) :: Contravariant f => f b -> (a -> b) -> f a infixl 4 >$$< -- | This is >$ with its arguments flipped. ($<) :: Contravariant f => f b -> b -> f a infixl 4 $< newtype Predicate a Predicate :: (a -> Bool) -> Predicate a [getPredicate] :: Predicate a -> a -> Bool -- | Defines a total ordering on a type as per compare. -- -- This condition is not checked by the types. You must ensure that the -- supplied values are valid total orderings yourself. newtype Comparison a Comparison :: (a -> a -> Ordering) -> Comparison a [getComparison] :: Comparison a -> a -> a -> Ordering -- | Compare using compare. defaultComparison :: Ord a => Comparison a -- | This data type represents an equivalence relation. -- -- Equivalence relations are expected to satisfy three laws: -- -- -- -- The types alone do not enforce these laws, so you'll have to check -- them yourself. newtype Equivalence a Equivalence :: (a -> a -> Bool) -> Equivalence a [getEquivalence] :: Equivalence a -> a -> a -> Bool -- | Check for equivalence with ==. -- -- Note: The instances for Double and Float violate -- reflexivity for NaN. defaultEquivalence :: Eq a => Equivalence a comparisonEquivalence :: Comparison a -> Equivalence a -- | Dual function arrows. newtype Op a b Op :: (b -> a) -> Op a b [getOp] :: Op a b -> b -> a instance Control.Category.Category Data.Functor.Contravariant.Op instance (Data.Functor.Contravariant.Contravariant f, Data.Functor.Contravariant.Contravariant g) => Data.Functor.Contravariant.Contravariant (f GHC.Generics.:*: g) instance (Data.Functor.Contravariant.Contravariant f, Data.Functor.Contravariant.Contravariant g) => Data.Functor.Contravariant.Contravariant (f GHC.Generics.:+: g) instance (GHC.Base.Functor f, Data.Functor.Contravariant.Contravariant g) => Data.Functor.Contravariant.Contravariant (f GHC.Generics.:.: g) instance Data.Functor.Contravariant.Contravariant f => Data.Functor.Contravariant.Contravariant (Data.Semigroup.Internal.Alt f) instance Data.Functor.Contravariant.Contravariant Data.Functor.Contravariant.Comparison instance (GHC.Base.Functor f, Data.Functor.Contravariant.Contravariant g) => Data.Functor.Contravariant.Contravariant (Data.Functor.Compose.Compose f g) instance Data.Functor.Contravariant.Contravariant (Data.Functor.Const.Const a) instance Data.Functor.Contravariant.Contravariant Data.Functor.Contravariant.Equivalence instance Data.Functor.Contravariant.Contravariant (GHC.Generics.K1 i c) instance Data.Functor.Contravariant.Contravariant f => Data.Functor.Contravariant.Contravariant (GHC.Generics.M1 i c f) instance Data.Functor.Contravariant.Contravariant (Data.Functor.Contravariant.Op a) instance Data.Functor.Contravariant.Contravariant Data.Functor.Contravariant.Predicate instance (Data.Functor.Contravariant.Contravariant f, Data.Functor.Contravariant.Contravariant g) => Data.Functor.Contravariant.Contravariant (Data.Functor.Product.Product f g) instance Data.Functor.Contravariant.Contravariant Data.Proxy.Proxy instance Data.Functor.Contravariant.Contravariant f => Data.Functor.Contravariant.Contravariant (GHC.Generics.Rec1 f) instance (Data.Functor.Contravariant.Contravariant f, Data.Functor.Contravariant.Contravariant g) => Data.Functor.Contravariant.Contravariant (Data.Functor.Sum.Sum f g) instance Data.Functor.Contravariant.Contravariant GHC.Generics.U1 instance Data.Functor.Contravariant.Contravariant GHC.Generics.V1 instance GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Contravariant.Op a b) instance GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Contravariant.Op a b) instance GHC.Base.Monoid (Data.Functor.Contravariant.Comparison a) instance GHC.Base.Monoid (Data.Functor.Contravariant.Equivalence a) instance GHC.Base.Monoid a => GHC.Base.Monoid (Data.Functor.Contravariant.Op a b) instance GHC.Base.Monoid (Data.Functor.Contravariant.Predicate a) instance GHC.Num.Num a => GHC.Num.Num (Data.Functor.Contravariant.Op a b) instance GHC.Base.Semigroup (Data.Functor.Contravariant.Comparison a) instance GHC.Base.Semigroup (Data.Functor.Contravariant.Equivalence a) instance GHC.Base.Semigroup a => GHC.Base.Semigroup (Data.Functor.Contravariant.Op a b) instance GHC.Base.Semigroup (Data.Functor.Contravariant.Predicate a) -- | A class of non-empty data structures that can be folded to a summary -- value. module Data.Foldable1 -- | Non-empty data structures that can be folded. class Foldable t => Foldable1 (t :: Type -> Type) -- | Given a structure with elements whose type is a Semigroup, -- combine them via the semigroup's (<>) operator. -- This fold is right-associative and lazy in the accumulator. When you -- need a strict left-associative fold, use foldMap1' instead, -- with id as the map. fold1 :: (Foldable1 t, Semigroup m) => t m -> m -- | Map each element of the structure to a semigroup, and combine the -- results with (<>). This fold is -- right-associative and lazy in the accumulator. For strict -- left-associative folds consider foldMap1' instead. -- --
--   >>> foldMap1 (:[]) (1 :| [2, 3, 4])
--   [1,2,3,4]
--   
foldMap1 :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m -- | A left-associative variant of foldMap1 that is strict in the -- accumulator. Use this for strict reduction when partial results are -- merged via (<>). -- --
--   >>> foldMap1' Sum (1 :| [2, 3, 4])
--   Sum {getSum = 10}
--   
foldMap1' :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m -- | NonEmpty list of elements of a structure, from left to right. -- --
--   >>> toNonEmpty (Identity 2)
--   2 :| []
--   
toNonEmpty :: Foldable1 t => t a -> NonEmpty a -- | The largest element of a non-empty structure. -- --
--   >>> maximum (32 :| [64, 8, 128, 16])
--   128
--   
maximum :: (Foldable1 t, Ord a) => t a -> a -- | The least element of a non-empty structure. -- --
--   >>> minimum (32 :| [64, 8, 128, 16])
--   8
--   
minimum :: (Foldable1 t, Ord a) => t a -> a -- | The first element of a non-empty structure. -- --
--   >>> head (1 :| [2, 3, 4])
--   1
--   
head :: Foldable1 t => t a -> a -- | The last element of a non-empty structure. -- --
--   >>> last (1 :| [2, 3, 4])
--   4
--   
last :: Foldable1 t => t a -> a -- | Right-associative fold of a structure, lazy in the accumulator. -- -- In case of NonEmpty lists, foldrMap1, when given a -- function f, a binary operator g, and a list, reduces -- the list using g from right to left applying f to -- the rightmost element: -- --
--   foldrMap1 f g (x1 :| [x2, ..., xn1, xn]) == x1 `g` (x2 `g` ... (xn1 `g` (f xn))...)
--   
-- -- Note that since the head of the resulting expression is produced by an -- application of g to the first element of the list, if -- g is lazy in its right argument, foldrMap1 can produce -- a terminating expression from an unbounded list. -- -- For a general Foldable1 structure this should be semantically -- identical to: -- --
--   foldrMap1 f g = foldrMap1 f g . toNonEmpty
--   
foldrMap1 :: Foldable1 t => (a -> 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 structure to a single strict result. -- -- For a general Foldable1 structure this should be semantically -- identical to: -- --
--   foldlMap1' f z = foldlMap1' f z . toNonEmpty
--   
foldlMap1' :: Foldable1 t => (a -> b) -> (b -> a -> b) -> t a -> b -- | Left-associative fold of a structure, lazy in the accumulator. This is -- rarely what you want, but can work well for structures with efficient -- right-to-left sequencing and an operator that is lazy in its left -- argument. -- -- In case of NonEmpty lists, foldlMap1, when given a -- function f, a binary operator g, and a list, reduces -- the list using g from left to right applying f to -- the leftmost element: -- --
--   foldlMap1 f g (x1 :| [x2, ..., xn]) == (...(((f x1) `g` x2) `g`...) `g` xn
--   
-- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldlMap1 -- will diverge if given an infinite list. -- -- If you want an efficient strict left-fold, you probably want to use -- foldlMap1' instead of foldlMap1. The reason for this is -- that the latter does not force the inner results (e.g. (f -- x1) `g` x2 in the above example) before applying them to the -- operator (e.g. to (`g` x3)). This results in a thunk chain -- <math> elements long, which then must be evaluated from the -- outside-in. -- -- For a general Foldable1 structure this should be semantically -- identical to: -- --
--   foldlMap1 f g = foldlMap1 f g . toNonEmpty
--   
foldlMap1 :: Foldable1 t => (a -> b) -> (b -> a -> b) -> t a -> b -- | foldrMap1' is a variant of foldrMap1 that performs -- strict reduction from right to left, i.e. starting with the right-most -- element. The input structure must be finite, otherwise -- foldrMap1' runs out of space (diverges). -- -- If you want a strict right fold in constant space, you need a -- structure that supports faster than <math> access to the -- right-most element. -- -- This method does not run in constant space for structures such as -- NonEmpty lists that don't support efficient right-to-left -- iteration and so require <math> space to perform right-to-left -- reduction. Use of this method with such a structure is a hint that the -- chosen structure may be a poor fit for the task at hand. If the order -- in which the elements are combined is not important, use -- foldlMap1' instead. foldrMap1' :: Foldable1 t => (a -> b) -> (a -> b -> b) -> t a -> b -- | A variant of foldrMap1 where the rightmost element maps to -- itself. foldr1 :: Foldable1 t => (a -> a -> a) -> t a -> a -- | A variant of foldrMap1' where the rightmost element maps to -- itself. foldr1' :: Foldable1 t => (a -> a -> a) -> t a -> a -- | A variant of foldlMap1 where the leftmost element maps to -- itself. foldl1 :: Foldable1 t => (a -> a -> a) -> t a -> a -- | A variant of foldlMap1' where the leftmost element maps to -- itself. foldl1' :: Foldable1 t => (a -> a -> a) -> t a -> a -- | Insert an m between each pair of t m. -- --
--   >>> intercalate1 ", " $ "hello" :| ["how", "are", "you"]
--   "hello, how, are, you"
--   
-- --
--   >>> intercalate1 ", " $ "hello" :| []
--   "hello"
--   
-- --
--   >>> intercalate1 mempty $ "I" :| ["Am", "Fine", "You?"]
--   "IAmFineYou?"
--   
intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m -- | Monadic fold over the elements of a non-empty structure, associating -- to the right, i.e. from right to left. foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a -- | Monadic fold over the elements of a non-empty structure, associating -- to the left, i.e. from left to right. foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a -- | Map variant of foldrM1. foldrMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b -- | Map variant of foldlM1. foldlMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b -- | The largest element of a non-empty structure with respect to the given -- comparison function. maximumBy :: Foldable1 t => (a -> a -> Ordering) -> t a -> a -- | The least element of a non-empty structure with respect to the given -- comparison function. minimumBy :: Foldable1 t => (a -> a -> Ordering) -> t a -> a instance (Data.Foldable1.Foldable1 f, Data.Foldable1.Foldable1 g) => Data.Foldable1.Foldable1 (f GHC.Generics.:*: g) instance (Data.Foldable1.Foldable1 f, Data.Foldable1.Foldable1 g) => Data.Foldable1.Foldable1 (f GHC.Generics.:+: g) instance (Data.Foldable1.Foldable1 f, Data.Foldable1.Foldable1 g) => Data.Foldable1.Foldable1 (f GHC.Generics.:.: g) instance Data.Foldable1.Foldable1 f => Data.Foldable1.Foldable1 (Data.Semigroup.Internal.Alt f) instance Data.Foldable1.Foldable1 f => Data.Foldable1.Foldable1 (Data.Monoid.Ap f) instance Data.Foldable1.Foldable1 Data.Complex.Complex instance (Data.Foldable1.Foldable1 f, Data.Foldable1.Foldable1 g) => Data.Foldable1.Foldable1 (Data.Functor.Compose.Compose f g) instance Data.Foldable1.Foldable1 Data.Ord.Down instance Data.Foldable1.Foldable1 Data.Semigroup.Internal.Dual instance Data.Foldable1.Foldable1 Data.Semigroup.First instance Data.Foldable1.Foldable1 Data.Functor.Identity.Identity instance Data.Foldable1.Foldable1 Data.Semigroup.Last instance Data.Foldable1.Foldable1 f => Data.Foldable1.Foldable1 (GHC.Generics.M1 i c f) instance Data.Foldable1.Foldable1 Data.Semigroup.Max instance Data.Foldable1.Foldable1 Data.Semigroup.Min instance Data.Foldable1.Foldable1 GHC.Base.NonEmpty instance Data.Foldable1.Foldable1 GHC.Generics.Par1 instance (Data.Foldable1.Foldable1 f, Data.Foldable1.Foldable1 g) => Data.Foldable1.Foldable1 (Data.Functor.Product.Product f g) instance Data.Foldable1.Foldable1 Data.Semigroup.Internal.Product instance Data.Foldable1.Foldable1 f => Data.Foldable1.Foldable1 (GHC.Generics.Rec1 f) instance Data.Foldable1.Foldable1 GHC.Tuple.Prim.Solo instance (Data.Foldable1.Foldable1 f, Data.Foldable1.Foldable1 g) => Data.Foldable1.Foldable1 (Data.Functor.Sum.Sum f g) instance Data.Foldable1.Foldable1 Data.Semigroup.Internal.Sum instance Data.Foldable1.Foldable1 ((,) a) instance Data.Foldable1.Foldable1 GHC.Generics.V1 instance GHC.Base.Semigroup (Data.Foldable1.FromMaybe b) instance GHC.Base.Semigroup a => GHC.Base.Semigroup (Data.Foldable1.JoinWith a) instance GHC.Base.Semigroup (Data.Foldable1.NonEmptyDList a) -- | Derived from primitive package. module Data.Array.Byte -- | Lifted wrapper for ByteArray#. -- -- Since ByteArray# is an unlifted type and not a member of kind -- Type, things like [ByteArray#] or IO -- ByteArray# are ill-typed. To work around this inconvenience this -- module provides a standard lifted wrapper, inhabiting Type. -- Clients are expected to use ByteArray in higher-level APIs, but -- wrap and unwrap ByteArray internally as they please and use -- functions from GHC.Exts. data ByteArray ByteArray :: ByteArray# -> ByteArray -- | Lifted wrapper for MutableByteArray#. -- -- Since MutableByteArray# is an unlifted type and not a member of -- kind Type, things like [MutableByteArray#] or IO -- MutableByteArray# are ill-typed. To work around this -- inconvenience this module provides a standard lifted wrapper, -- inhabiting Type. Clients are expected to use -- MutableByteArray in higher-level APIs, but wrap and unwrap -- MutableByteArray internally as they please and use functions -- from GHC.Exts. data MutableByteArray s MutableByteArray :: MutableByteArray# s -> MutableByteArray s instance Data.Data.Data Data.Array.Byte.ByteArray instance Data.Typeable.Internal.Typeable s => Data.Data.Data (Data.Array.Byte.MutableByteArray s) instance GHC.Classes.Eq Data.Array.Byte.ByteArray instance GHC.Classes.Eq (Data.Array.Byte.MutableByteArray s) instance GHC.IsList.IsList Data.Array.Byte.ByteArray instance GHC.Base.Monoid Data.Array.Byte.ByteArray instance GHC.Classes.Ord Data.Array.Byte.ByteArray instance GHC.Base.Semigroup Data.Array.Byte.ByteArray instance GHC.Show.Show Data.Array.Byte.ByteArray