-- 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.14.0.0 -- | 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.Ord a => GHC.Classes.Ord (GHC.Maybe.Maybe a) instance GHC.Classes.Eq a => GHC.Classes.Eq (GHC.Maybe.Maybe a) -- | The arbitrary-precision Natural number type. -- -- Note: This is an internal GHC module with an API subject to -- change. It's recommended use the Numeric.Natural module to -- import the Natural type. module GHC.Natural -- | Type representing arbitrary-precision non-negative integers. -- --
-- >>> 2^100 :: Natural -- 1267650600228229401496703205376 ---- -- Operations whose result would be negative throw -- (Underflow :: ArithException), -- --
-- >>> -1 :: Natural -- *** Exception: arithmetic underflow --data Natural -- | in [0, maxBound::Word] NatS# :: GmpLimb# -> Natural -- | in ]maxBound::Word, +inf[ -- -- Invariant: NatJ# is used iff value doesn't fit in -- NatS# constructor. NB: Order of constructors *must* coincide -- with Ord relation NatJ# :: {-# UNPACK #-} !BigNat -> Natural -- | Construct Natural value from list of Words. -- -- This function is used by GHC for constructing Natural literals. 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 naturalToInt :: Natural -> Int naturalFromInteger :: Integer -> Natural -- | Construct Natural from Word value. wordToNatural :: Word -> Natural -- | Convert Int to Natural. Throws Underflow when -- passed a negative Int. intToNatural :: Int -> Natural -- | Try downcasting Natural to Word value. Returns -- Nothing if value doesn't fit in Word. naturalToWordMaybe :: Natural -> Maybe Word -- | Convert a Word# into a Natural -- -- Built-in rule ensures that applications of this function to literal -- Word# are lifted into Natural literals. wordToNatural# :: Word# -> Natural -- | Convert a Word# into a Natural -- -- In base we can't use wordToNatural# as built-in rules transform some -- of them into Natural literals. Use this function instead. wordToNaturalBase :: Word# -> Natural -- | "powModNatural b e m" computes -- base b raised to exponent e modulo -- m. powModNatural :: Natural -> Natural -> Natural -> Natural instance GHC.Classes.Ord GHC.Natural.Natural instance GHC.Classes.Eq GHC.Natural.Natural -- | 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>:2:1 in interactive:Ghci1 ---- -- GHC solves HasCallStack constraints in three steps: -- --
-- 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 :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => [Char] -> a -- | A variant of error that does not produce a stack trace. errorWithoutStackTrace :: forall (r :: RuntimeRep). forall (a :: TYPE r). [Char] -> a -- | A special case of error. It is expected that compilers will -- recognize this and insert error messages which are more appropriate to -- the context in which undefined appears. undefined :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => a -- | Basic data types and classes. module GHC.Base -- | A list producer that can be fused with foldr. This function is -- merely -- --
-- augment g xs = g (:) xs ---- -- but GHC's simplifier will transform an expression of the form -- foldr k z (augment g xs), which may arise after -- inlining, to g k (foldr k z xs), which avoids -- producing an intermediate list. augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] -- | Append two lists, i.e., -- --
-- [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] -- [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...] ---- -- If the first list is not finite, the result is the first list. (++) :: [a] -> [a] -> [a] infixr 5 ++ -- | A list producer that can be fused with foldr. This function is -- merely -- --
-- build g = g (:) [] ---- -- but GHC's simplifier will transform an expression of the form -- foldr k z (build g), which may arise after -- inlining, to g k z, which avoids producing an intermediate -- list. build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -- | 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 -- | This String equality predicate is used when desugaring -- pattern-matches against strings. eqString :: String -> String -> Bool bindIO :: IO a -> (a -> IO b) -> IO b returnIO :: a -> IO a -- | otherwise is defined as the value True. It helps to make -- guards more readable. eg. -- --
-- f x | x < 0 = ... -- | otherwise = ... --otherwise :: Bool -- | If the first argument evaluates to True, then the result is the -- second argument. Otherwise an AssertionFailed exception is -- raised, containing a String with the source file and line -- number of the call to assert. -- -- Assertions can normally be turned on or off with a compiler flag (for -- GHC, assertions are normally on unless optimisation is turned on with -- -O or the -fignore-asserts option is given). When -- assertions are turned off, the first argument to assert is -- ignored, and the second argument is returned as the result. assert :: Bool -> a -> a thenIO :: IO a -> IO b -> IO b breakpoint :: a -> a breakpointCond :: Bool -> a -> a -- | <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, ...] ---- --
-- >>> map (+1) [1, 2, 3] -- [2,3,4] --map :: (a -> b) -> [a] -> [b] -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ has low, right-associative binding precedence, so it -- sometimes allows parentheses to be omitted; for example: -- --
-- f $ g $ h x = f (g (h x)) ---- -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. -- -- Note that ($) is levity-polymorphic in its result -- type, so that foo $ True where foo :: Bool -> -- Int# is well-typed. ($) :: forall r a (b :: TYPE r). (a -> b) -> a -> b infixr 0 $ -- | 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 ---- --
-- 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 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: -- --
-- do a <- as -- bs a --(>>=) :: forall a b. Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. -- -- 'as >> bs' can be understood as the do -- expression -- --
-- do as -- bs --(>>) :: forall a b. 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 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. class Functor f -- | Using ApplicativeDo: 'fmap f as' can be -- understood as the do expression -- --
-- do a <- as -- pure (f a) ---- -- with an inferred Functor constraint. 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. -- -- Using ApplicativeDo: 'a <$ bs' can be -- understood as the do expression -- --
-- do bs -- pure a ---- -- with an inferred Functor constraint. (<$) :: Functor f => a -> f b -> f a infixl 4 <$ -- | A functor with application, providing operations to -- --
-- (<*>) = liftA2 id ---- --
-- liftA2 f x y = f <$> x <*> y ---- -- Further, any definition must satisfy the following: -- --
pure id <*> v = -- v
pure (.) <*> u -- <*> v <*> w = u <*> (v -- <*> w)
pure f <*> -- pure x = pure (f x)
u <*> pure y = -- pure ($ y) <*> u
-- forall x y. p (q x y) = f x . g y ---- -- it follows from the above that -- --
-- liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v ---- -- If f is also a Monad, it should satisfy -- -- -- -- (which implies that pure and <*> satisfy the -- applicative functor laws). class Functor f => Applicative f -- | Lift a value. pure :: Applicative f => a -> f a -- | Sequential application. -- -- A few functors support an implementation of <*> that is -- more efficient than the default one. -- -- Using ApplicativeDo: 'fs <*> as' can be -- understood as the do expression -- --
-- do f <- fs -- a <- as -- pure (f a) --(<*>) :: 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. -- -- Using ApplicativeDo: 'liftA2 f as bs' can be -- understood as the do expression -- --
-- do a <- as -- b <- bs -- pure (f a b) --liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c -- | Sequence actions, discarding the value of the first argument. -- -- 'as *> bs' can be understood as the do -- expression -- --
-- do as -- bs ---- -- This is a tad complicated for our ApplicativeDo extension -- which will give it a Monad constraint. For an -- Applicative constraint we write it of the form -- --
-- do _ <- as -- b <- bs -- pure b --(*>) :: Applicative f => f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. -- -- Using ApplicativeDo: 'as <* bs' can be -- understood as the do expression -- --
-- do a <- as -- bs -- pure a --(<*) :: Applicative f => f a -> f b -> f a infixl 4 <* infixl 4 *> infixl 4 <*> -- | The class of semigroups (types with an associative binary operation). -- -- Instances should satisfy the following: -- -- class Semigroup a -- | An associative operation. -- --
-- >>> [1,2,3] <> [4,5,6] -- [1,2,3,4,5,6] --(<>) :: Semigroup a => a -> a -> a -- | Reduce a non-empty list with <> -- -- The default definition should be sufficient, but this can be -- overridden for efficiency. -- --
-- >>> import Data.List.NonEmpty -- -- >>> sconcat $ "Hello" :| [" ", "Haskell", "!"] -- "Hello Haskell!" --sconcat :: Semigroup a => NonEmpty a -> a -- | Repeat a value n times. -- -- Given that this works on a Semigroup it is allowed to fail if -- you request 0 or fewer repetitions, and the default definition will do -- so. -- -- By making this a member of the class, idempotent semigroups and -- monoids can upgrade this to execute in <math> by picking -- stimes = stimesIdempotent or stimes = -- stimesIdempotentMonoid respectively. -- --
-- >>> stimes 4 [1] -- [1,1,1,1] --stimes :: (Semigroup a, Integral b) => b -> a -> a infixr 6 <> -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following: -- --
-- >>> "Hello world" <> mempty -- "Hello world" --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 data Opaque O :: a -> Opaque -- | A String is a list of characters. String constants in Haskell -- are values of type String. -- -- See Data.List for operations on lists. type String = [Char] -- | Non-empty (and non-strict) list type. data NonEmpty a (:|) :: a -> [a] -> NonEmpty a infixr 5 :| -- | Monads that also support choice and failure. class (Alternative m, Monad m) => MonadPlus m -- | The identity of mplus. It should also satisfy the equations -- --
-- mzero >>= f = mzero -- v >> mzero = mzero ---- -- 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 -- | A monoid on applicative functors. -- -- If defined, some and many should be the least solutions -- of the equations: -- -- class Applicative f => Alternative f -- | The identity of <|> empty :: Alternative f => f a -- | An associative binary operation (<|>) :: Alternative f => f a -> f a -> f a -- | One or more. some :: Alternative f => f a -> f [a] -- | Zero or more. many :: Alternative f => f a -> f [a] infixl 3 <|> -- | A variant of <*> with the arguments reversed. -- -- Using ApplicativeDo: 'as <**> fs' can -- be understood as the do expression -- --
-- do a <- as -- f <- fs -- pure (f a) --(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 <**> -- | Lift a function to actions. This function may be used as a value for -- fmap in a Functor instance. -- -- Using ApplicativeDo: 'liftA f as' can be -- understood as the do expression -- --
-- do a <- as -- pure (f a) ---- -- with an inferred Functor constraint, weaker than -- Applicative. liftA :: Applicative f => (a -> b) -> f a -> f b -- | Lift a ternary function to actions. -- -- Using ApplicativeDo: 'liftA3 f as bs cs' can -- be understood as the do expression -- --
-- do a <- as -- b <- bs -- c <- cs -- pure (f a b c) --liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | 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 () -- | Evaluate each action in the sequence from left to right, and collect -- the results. sequence :: Monad m => [m a] -> m [a] -- | mapM f is equivalent to sequence . -- map f. mapM :: Monad m => (a -> m b) -> [a] -> m [b] -- | 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 mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst unsafeChr :: Int -> Char -- | The fromEnum method restricted to the type Char. ord :: Char -> Int minInt :: Int maxInt :: Int -- | Identity function. -- --
-- id x = x --id :: a -> a -- | const x is a unary function which evaluates to x for -- all inputs. -- --
-- >>> const 42 "hello" -- 42 ---- --
-- >>> map (const 42) [0..3] -- [42,42,42,42] --const :: a -> b -> a -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | flip f takes its (first) two arguments in the reverse -- order of f. -- --
-- >>> flip (++) "hello" "world" -- "worldhello" --flip :: (a -> b -> c) -> b -> a -> c -- | 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. ($!) :: forall r a (b :: TYPE r). (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 failIO :: String -> IO a unIO :: IO a -> State# RealWorld -> (# State# RealWorld, a #) -- | Returns the tag of a constructor application; this function is used by -- the deriving code for Eq, Ord and Enum. getTag :: a -> Int# quotInt :: Int -> Int -> Int remInt :: Int -> Int -> Int divInt :: Int -> Int -> Int modInt :: Int -> Int -> Int quotRemInt :: Int -> Int -> (Int, Int) divModInt :: Int -> Int -> (Int, Int) divModInt# :: Int# -> Int# -> (# Int#, Int# #) -- | Shift the argument left by the specified number of bits (which must be -- non-negative). shiftL# :: Word# -> Int# -> Word# -- | Shift the argument right by the specified number of bits (which must -- be non-negative). The RL means "right, logical" (as opposed to -- RA for arithmetic) (although an arithmetic right shift wouldn't make -- sense for Word#) shiftRL# :: Word# -> Int# -> Word# -- | Shift the argument left by the specified number of bits (which must be -- non-negative). iShiftL# :: Int# -> Int# -> Int# -- | Shift the argument right (signed) by the specified number of bits -- (which must be non-negative). The RA means "right, arithmetic" -- (as opposed to RL for logical) iShiftRA# :: Int# -> Int# -> Int# -- | Shift the argument right (unsigned) by the specified number of bits -- (which must be non-negative). The RL means "right, logical" (as -- opposed to RA for arithmetic) iShiftRL# :: Int# -> Int# -> Int# instance GHC.Classes.Ord a => GHC.Classes.Ord (GHC.Base.NonEmpty a) instance GHC.Classes.Eq a => GHC.Classes.Eq (GHC.Base.NonEmpty a) instance GHC.Base.Monoid [a] instance GHC.Base.Monoid b => GHC.Base.Monoid (a -> b) instance GHC.Base.Monoid () 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 GHC.Types.Ordering instance GHC.Base.Semigroup a => GHC.Base.Monoid (GHC.Maybe.Maybe a) instance GHC.Base.Monoid a => GHC.Base.Applicative ((,) a) instance GHC.Base.Monoid a => GHC.Base.Monad ((,) 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.Monad ((,,) a b) instance (GHC.Base.Monoid a, GHC.Base.Monoid b, GHC.Base.Monoid c) => GHC.Base.Applicative ((,,,) a b c) instance (GHC.Base.Monoid a, GHC.Base.Monoid b, GHC.Base.Monoid c) => GHC.Base.Monad ((,,,) a b c) instance GHC.Base.Monoid a => GHC.Base.Monoid (GHC.Types.IO a) instance GHC.Base.Semigroup [a] instance GHC.Base.Semigroup (GHC.Base.NonEmpty a) instance GHC.Base.Semigroup b => GHC.Base.Semigroup (a -> b) instance GHC.Base.Semigroup () 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 GHC.Types.Ordering instance GHC.Base.Semigroup a => GHC.Base.Semigroup (GHC.Maybe.Maybe a) instance GHC.Base.Semigroup a => GHC.Base.Semigroup (GHC.Types.IO a) instance GHC.Base.Functor GHC.Base.NonEmpty instance GHC.Base.Applicative GHC.Base.NonEmpty instance GHC.Base.Monad GHC.Base.NonEmpty instance GHC.Base.MonadPlus GHC.Maybe.Maybe instance GHC.Base.MonadPlus [] instance GHC.Base.MonadPlus GHC.Types.IO instance GHC.Base.Alternative GHC.Maybe.Maybe instance GHC.Base.Alternative [] instance GHC.Base.Alternative GHC.Types.IO instance GHC.Base.Monad ((->) r) instance GHC.Base.Monad GHC.Maybe.Maybe instance GHC.Base.Monad [] instance GHC.Base.Functor GHC.Types.IO instance GHC.Base.Monad GHC.Types.IO instance GHC.Base.Applicative ((->) r) instance GHC.Base.Applicative GHC.Maybe.Maybe instance GHC.Base.Applicative [] instance GHC.Base.Applicative GHC.Types.IO instance GHC.Base.Functor ((,,) a b) instance GHC.Base.Functor ((,,,) a b c) instance GHC.Base.Functor ((->) r) instance GHC.Base.Functor ((,) a) instance GHC.Base.Functor GHC.Maybe.Maybe instance GHC.Base.Functor [] module GHC.Profiling -- | Stop attributing ticks to cost centres. Allocations will still be -- attributed. stopProfTimer :: IO () -- | Start attributing ticks to cost centres. This is called by the RTS on -- startup. startProfTimer :: IO () -- | 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: -- --
-- 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 * -- | 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 instance GHC.Num.Num GHC.Types.Int instance GHC.Num.Num GHC.Types.Word instance GHC.Num.Num GHC.Integer.Type.Integer instance GHC.Num.Num GHC.Natural.Natural -- | 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: -- --
-- 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: -- --
-- test :: IORef [a] -- test = unsafePerformIO $ newIORef [] -- -- main = do -- writeIORef test [42] -- bang <- readIORef test -- print (bang :: [Char]) ---- -- This program will core dump. This problem with polymorphic references -- is well known in the ML community, and does not arise with normal -- monadic use of references. There is no easy way to make it impossible -- once you use unsafePerformIO. Indeed, it is possible to write -- coerce :: a -> b with the help of unsafePerformIO. -- So be careful! unsafePerformIO :: IO a -> a -- | 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 ghciStepIO :: GHCiSandboxIO m => m a -> IO a -- | A monad that doesn't allow any IO. data NoIO a instance GHC.Base.Functor GHC.GHCi.NoIO instance GHC.Base.Applicative GHC.GHCi.NoIO instance GHC.Base.Monad GHC.GHCi.NoIO instance GHC.GHCi.GHCiSandboxIO GHC.GHCi.NoIO instance GHC.GHCi.GHCiSandboxIO GHC.Types.IO -- | 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 -- | Extract the first component of a pair. fst :: (a, b) -> a -- | Extract the second component of a pair. snd :: (a, b) -> b -- | curry converts an uncurried function to a curried function. -- --
-- >>> curry fst 1 2 -- 1 --curry :: ((a, b) -> c) -> a -> b -> c -- | uncurry converts a curried function to a function on pairs. -- --
-- >>> 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. -- --
-- >>> 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. class Functor f -- | Using ApplicativeDo: 'fmap f as' can be -- understood as the do expression -- --
-- do a <- as -- pure (f a) ---- -- with an inferred Functor constraint. 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. -- -- Using ApplicativeDo: 'a <$ bs' can be -- understood as the do expression -- --
-- do bs -- pure a ---- -- with an inferred Functor constraint. (<$) :: Functor f => a -> f b -> f a infixl 4 <$ -- | Flipped version of <$. -- -- Using ApplicativeDo: 'as $> b' can be -- understood as the do expression -- --
-- do as -- pure b ---- -- with an inferred Functor constraint. -- --
-- >>> 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. -- --
-- >>> 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 ---- --
-- >>> 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 <&> -- | void value discards or ignores the result of -- evaluation, such as the return value of an IO action. -- -- Using ApplicativeDo: 'void as' can be -- understood as the do expression -- --
-- do as -- pure () ---- -- with an inferred Functor constraint. -- --
-- >>> void Nothing -- Nothing -- -- >>> void (Just 3) -- Just () ---- -- Replace the contents of an Either Int -- Int with unit, resulting in an Either -- Int '()': -- --
-- >>> void (Left 8675309) -- Left 8675309 -- -- >>> void (Right 8675309) -- Right () ---- -- Replace every element of a list with unit: -- --
-- >>> void [1,2,3] -- [(),(),()] ---- -- Replace the second element of a pair with unit: -- --
-- >>> void (1,2) -- (1,()) ---- -- Discard the result of an IO action: -- --
-- >>> mapM print [1,2] -- 1 -- 2 -- [(),()] -- -- >>> void $ mapM print [1,2] -- 1 -- 2 --void :: Functor f => f a -> f () -- | Simple combinators working solely on and with functions. module Data.Function -- | Identity function. -- --
-- id x = x --id :: a -> a -- | const x is a unary function which evaluates to x for -- all inputs. -- --
-- >>> const 42 "hello" -- 42 ---- --
-- >>> map (const 42) [0..3] -- [42,42,42,42] --const :: a -> b -> a -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | flip f takes its (first) two arguments in the reverse -- order of f. -- --
-- >>> flip (++) "hello" "world" -- "worldhello" --flip :: (a -> b -> c) -> b -> a -> c -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ has low, right-associative binding precedence, so it -- sometimes allows parentheses to be omitted; for example: -- --
-- f $ g $ h x = f (g (h x)) ---- -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. -- -- Note that ($) is levity-polymorphic in its result -- type, so that foo $ True where foo :: Bool -> -- Int# is well-typed. ($) :: forall r a (b :: TYPE r). (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 $. -- --
-- >>> 5 & (+1) & show -- "6" --(&) :: 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. -- -- For example, 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, -- --
-- >>> fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5 -- 120 ---- -- 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 :: (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. -- --
-- ((+) `on` f) x y = f x + f y ---- -- Typical usage: sortBy (compare `on` -- fst). -- -- Algebraic properties: -- --
(*) `on` id = (*) -- (if (*) ∉ {⊥, const -- ⊥})
((*) `on` f) `on` g = (*) `on` (f . g)
flip on f . flip on g = flip on (g . -- f)
-- 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. -- --
-- >>> 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 tru fls -- | Type-level "and" type family a && b infixr 3 && -- | Type-level "or" type family a || b infixr 2 || -- | Type-level "not". An injective type family since 4.10.0.0. type family Not a = res | res -> 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://prime.haskell.org/wiki/Libraries/Proposals/MonadFail -- for more details. module Control.Monad.Fail -- | When a value is bound in do-notation, the pattern on the left -- hand side of <- might not match. In this case, this class -- provides a function to recover. -- -- A Monad without a MonadFail instance may only be used in -- conjunction with pattern that always match, such as newtypes, tuples, -- data types with only a single data constructor, and irrefutable -- patterns (~pat). -- -- Instances of MonadFail should satisfy the following law: -- fail s should be a left zero for >>=, -- --
-- fail s >>= f = fail s ---- -- If your Monad is also MonadPlus, a popular definition is -- --
-- fail _ = mzero --class Monad m => MonadFail m fail :: MonadFail m => String -> m a instance Control.Monad.Fail.MonadFail GHC.Maybe.Maybe instance Control.Monad.Fail.MonadFail [] instance Control.Monad.Fail.MonadFail GHC.Types.IO -- | 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. -- --
-- >>> 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 _. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> fromJust (Just 1) -- 1 ---- --
-- >>> 2 * (fromJust (Just 10)) -- 20 ---- --
-- >>> 2 * (fromJust Nothing) -- *** Exception: Maybe.fromJust: Nothing --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 -- values; otherwise, it returns the value contained in the Maybe. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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 -- | <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, ...] ---- --
-- >>> map (+1) [1, 2, 3] -- [2,3,4] --map :: (a -> b) -> [a] -> [b] -- | Append two lists, i.e., -- --
-- [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] -- [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...] ---- -- If the first list is not finite, the result is the first list. (++) :: [a] -> [a] -> [a] infixr 5 ++ -- | <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] ---- --
-- >>> filter odd [1, 2, 3] -- [1,3] --filter :: (a -> Bool) -> [a] -> [a] -- | Concatenate a list of lists. -- --
-- >>> concat [] -- [] -- -- >>> concat [[42]] -- [42] -- -- >>> concat [[1,2,3], [4,5], [6], []] -- [1,2,3,4,5,6] --concat :: [[a]] -> [a] -- | <math>. Extract the first element of a list, which must be -- non-empty. -- --
-- >>> head [1, 2, 3] -- 1 -- -- >>> head [1..] -- 1 -- -- >>> head [] -- Exception: Prelude.head: empty list --head :: [a] -> a -- | <math>. Extract the last element of a list, which must be finite -- and non-empty. -- --
-- >>> last [1, 2, 3] -- 3 -- -- >>> last [1..] -- * Hangs forever * -- -- >>> last [] -- Exception: Prelude.last: empty list --last :: [a] -> a -- | <math>. Extract the elements after the head of a list, which -- must be non-empty. -- --
-- >>> tail [1, 2, 3] -- [2,3] -- -- >>> tail [1] -- [] -- -- >>> tail [] -- Exception: Prelude.tail: empty list --tail :: [a] -> [a] -- | <math>. Return all the elements of a list except the last one. -- The list must be non-empty. -- --
-- >>> init [1, 2, 3] -- [1,2] -- -- >>> init [1] -- [] -- -- >>> init [] -- Exception: Prelude.init: empty list --init :: [a] -> [a] -- | <math>. Decompose a list into its head and tail. -- --
-- >>> uncons [] -- Nothing -- -- >>> uncons [1] -- Just (1,[]) -- -- >>> uncons [1, 2, 3] -- Just (1,[2,3]) --uncons :: [a] -> Maybe (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 -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. -- --
-- >>> ['a', '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 --(!!) :: [a] -> Int -> a infixl 9 !! -- | 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 :: (a -> a -> a) -> [a] -> a -- | A strict version of foldl1. foldl1' :: (a -> a -> a) -> [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 ---- --
-- >>> 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"] -- -- >>> scanl (+) 0 [1..] -- * Hangs forever * --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, ...] ---- --
-- >>> 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] -- -- >>> scanl1 (+) [1..] -- * Hangs forever * --scanl1 :: (a -> a -> a) -> [a] -> [a] -- | <math>. A strict version of scanl. scanl' :: (b -> a -> b) -> b -> [a] -> [b] -- | 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 -- -- >>> foldr1 (+) [1..] -- * Hangs forever * --foldr1 :: (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. ---- --
-- >>> 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"] -- -- >>> scanr (+) 0 [1..] -- * Hangs forever * --scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | <math>. scanr1 is a variant of scanr that has no -- starting value argument. -- --
-- >>> 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] -- -- >>> scanr1 (+) [1..] -- * Hangs forever * --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), ...] ---- -- 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. -- --
-- >>> iterate not True -- [True,False,True,False... -- -- >>> iterate (+3) 42 -- [42,45,48,51,54,57,60,63... --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. iterate' :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. -- --
-- >>> repeat 17 -- [17,17,17,17,17,17,17,17,17... --repeat :: a -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. -- --
-- >>> replicate 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. -- --
-- >>> cycle [] -- Exception: Prelude.cycle: empty list -- -- >>> cycle [42] -- [42,42,42,42,42,42,42,42,42,42... -- -- >>> cycle [2, 5, 7] -- [2,5,7,2,5,7,2,5,7,2,5,7... --cycle :: [a] -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n > length xs. -- --
-- >>> take 5 "Hello World!" -- "Hello" -- -- >>> take 3 [1,2,3,4,5] -- [1,2,3] -- -- >>> take 3 [1,2] -- [1,2] -- -- >>> take 3 [] -- [] -- -- >>> take (-1) [1,2] -- [] -- -- >>> take 0 [1,2] -- [] ---- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. take :: Int -> [a] -> [a] -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n > length -- xs. -- --
-- >>> drop 6 "Hello World!" -- "World!" -- -- >>> drop 3 [1,2,3,4,5] -- [4,5] -- -- >>> drop 3 [1,2] -- [] -- -- >>> drop 3 [] -- [] -- -- >>> drop (-1) [1,2] -- [1,2] -- -- >>> drop 0 [1,2] -- [1,2] ---- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. drop :: Int -> [a] -> [a] -- | 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 => [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 => [a] -> a -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
-- >>> splitAt 6 "Hello World!" -- ("Hello ","World!") -- -- >>> splitAt 3 [1,2,3,4,5] -- ([1,2,3],[4,5]) -- -- >>> splitAt 1 [1,2,3] -- ([1],[2,3]) -- -- >>> splitAt 3 [1,2,3] -- ([1,2,3],[]) -- -- >>> splitAt 4 [1,2,3] -- ([1,2,3],[]) -- -- >>> splitAt 0 [1,2,3] -- ([],[1,2,3]) -- -- >>> splitAt (-1) [1,2,3] -- ([],[1,2,3]) ---- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) -- | takeWhile, applied to a predicate p and a list -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p. -- --
-- >>> takeWhile (< 3) [1,2,3,4,1,2,3,4] -- [1,2] -- -- >>> takeWhile (< 9) [1,2,3] -- [1,2,3] -- -- >>> takeWhile (< 0) [1,2,3] -- [] --takeWhile :: (a -> Bool) -> [a] -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. -- --
-- >>> dropWhile (< 3) [1,2,3,4,5,1,2,3] -- [3,4,5,1,2,3] -- -- >>> dropWhile (< 9) [1,2,3] -- [] -- -- >>> dropWhile (< 0) [1,2,3] -- [1,2,3] --dropWhile :: (a -> Bool) -> [a] -> [a] -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is longest prefix (possibly empty) -- of xs of elements that satisfy p and second element -- is the remainder of the list: -- --
-- >>> span (< 3) [1,2,3,4,1,2,3,4] -- ([1,2],[3,4,1,2,3,4]) -- -- >>> span (< 9) [1,2,3] -- ([1,2,3],[]) -- -- >>> span (< 0) [1,2,3] -- ([],[1,2,3]) ---- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | break, applied to a predicate p and a list -- xs, returns a tuple where first element is longest prefix -- (possibly empty) of xs of elements that do not satisfy -- p and second element is the remainder of the list: -- --
-- >>> break (> 3) [1,2,3,4,1,2,3,4] -- ([1,2,3],[4,1,2,3,4]) -- -- >>> break (< 9) [1,2,3] -- ([],[1,2,3]) -- -- >>> break (> 9) [1,2,3] -- ([1,2,3],[]) ---- -- break p is equivalent to span (not . -- p). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. -- --
-- >>> reverse [] -- [] -- -- >>> reverse [42] -- [42] -- -- >>> reverse [2,5,7] -- [7,5,2] -- -- >>> reverse [1..] -- * Hangs forever * --reverse :: [a] -> [a] -- | and returns the conjunction of a Boolean list. For the result -- to be True, the list must be finite; False, however, -- results from a False value at a finite index of a finite or -- infinite list. -- --
-- >>> and [] -- 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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 -- | 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. -- --
-- >>> 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. -- --
-- >>> 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` -- | <math>. lookup key assocs looks up a key in an -- association list. -- --
-- >>> 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 -- | 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 ---- --
-- >>> concatMap (\i -> [-i,i]) [] -- [] -- -- >>> concatMap (\i -> [-i,i]) [1,2,3] -- [-1,1,-2,2,-3,3] --concatMap :: (a -> [b]) -> [a] -> [b] -- | <math>. zip takes two lists and returns a list of -- corresponding pairs. -- --
-- >>> zip [1, 2] ['a', 'b'] -- [(1, 'a'), (2, 'b')] ---- -- 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 is right-lazy: -- --
-- >>> zip [] _|_ -- [] -- -- >>> zip _|_ [] -- _|_ ---- -- zip is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. 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..] ---- -- For example, zipWith (+) is applied to two lists to -- produce the list of corresponding sums: -- --
-- >>> zipWith (+) [1, 2, 3] [4, 5, 6] -- [5,7,9] ---- -- zipWith is right-lazy: -- --
-- >>> zipWith f [] _|_ -- [] ---- -- zipWith is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | The zipWith3 function takes a function which combines three -- elements, as well as three lists and returns a list of 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..] --zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] -- | unzip transforms a list of pairs into a list of first -- components and a list of second components. -- --
-- >>> unzip [] -- ([],[]) -- -- >>> 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, analogous to unzip. -- --
-- >>> unzip3 [] -- ([],[],[]) -- -- >>> unzip3 [(1, 'a', True), (2, 'b', False)] -- ([1,2],"ab",[True,False]) --unzip3 :: [(a, b, c)] -> ([a], [b], [c]) errorEmptyList :: String -> 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: -- --
-- 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, -- --
-- 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 () instance GHC.Show.Show GHC.Types.Bool instance GHC.Show.Show GHC.Types.Ordering instance GHC.Show.Show a => GHC.Show.Show (GHC.Maybe.Maybe a) instance GHC.Show.Show a => GHC.Show.Show (GHC.Base.NonEmpty a) instance GHC.Show.Show GHC.Stack.Types.SrcLoc instance GHC.Show.Show GHC.Types.RuntimeRep instance GHC.Show.Show GHC.Types.VecCount instance GHC.Show.Show GHC.Types.VecElem instance GHC.Show.Show GHC.Types.TypeLitSort instance GHC.Show.Show a => GHC.Show.Show [a] instance GHC.Show.Show GHC.Types.Char instance GHC.Show.Show GHC.Types.Int instance GHC.Show.Show GHC.Types.Word instance GHC.Show.Show GHC.Types.TyCon instance GHC.Show.Show GHC.Types.TrName instance GHC.Show.Show GHC.Types.Module instance GHC.Show.Show GHC.Stack.Types.CallStack 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 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 GHC.Integer.Type.Integer instance GHC.Show.Show GHC.Natural.Natural instance GHC.Show.Show GHC.Types.KindRep -- | 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 -- --
-- 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.Functor (GHC.ST.ST s) instance GHC.Base.Applicative (GHC.ST.ST s) instance GHC.Base.Monad (GHC.ST.ST s) instance Control.Monad.Fail.MonadFail (GHC.ST.ST s) instance GHC.Base.Semigroup a => GHC.Base.Semigroup (GHC.ST.ST s a) instance GHC.Base.Monoid a => GHC.Base.Monoid (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 4 :: [Integer] = [4,5,6,7,...]
enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: -- Int]
enumFromThen 4 6 :: [Integer] = [4,6,8,10...]
enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: -- Int]
enumFromTo 6 10 :: [Int] = [6,7,8,9,10]
enumFromTo 42 1 :: [Integer] = []
enumFromThenTo 4 2 -6 :: [Integer] = -- [4,2,0,-2,-4,-6]
enumFromThenTo 6 8 2 :: [Int] = []
-- (x `quot` y)*y + (x `rem` y) == x --rem :: Integral a => a -> a -> a -- | integer division truncated toward negative infinity div :: Integral a => a -> a -> a -- | integer modulus, satisfying -- --
-- (x `div` y)*y + (x `mod` y) == x --mod :: Integral a => a -> a -> a -- | simultaneous quot and rem quotRem :: Integral a => a -> a -> (a, a) -- | simultaneous div and mod divMod :: Integral a => a -> a -> (a, a) -- | conversion to Integer toInteger :: Integral a => a -> Integer infixl 7 `mod` infixl 7 `rem` infixl 7 `quot` infixl 7 `div` -- | 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: -- --
-- 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 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.Classes.Eq (GHC.Arr.STArray s i e) instance GHC.Base.Functor (GHC.Arr.Array i) instance (GHC.Ix.Ix i, GHC.Classes.Eq e) => GHC.Classes.Eq (GHC.Arr.Array i e) 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 Data.Bits -- | The Bits class defines bitwise operations over integral types. -- --
clearBit zeroBits n == -- zeroBits
setBit zeroBits n == bit -- n
testBit zeroBits n == False
popCount zeroBits == 0
-- finiteBitSize = bitSize -- bitSizeMaybe = Just . finiteBitSize --finiteBitSize :: FiniteBits b => b -> Int -- | Count number of zero bits preceding the most significant set bit. -- --
-- countLeadingZeros (zeroBits :: a) = finiteBitSize (zeroBits :: a) ---- -- countLeadingZeros can be used to compute log base 2 via -- --
-- logBase2 x = finiteBitSize x - 1 - countLeadingZeros x ---- -- Note: The default implementation for this method is intentionally -- naive. However, the instances provided for the primitive integral -- types are implemented using CPU specific machine instructions. countLeadingZeros :: FiniteBits b => b -> Int -- | Count number of zero bits following the least significant set bit. -- --
-- countTrailingZeros (zeroBits :: a) = finiteBitSize (zeroBits :: a) -- countTrailingZeros . negate = countTrailingZeros ---- -- The related find-first-set operation can be expressed in terms -- of countTrailingZeros as follows -- --
-- findFirstSet x = 1 + countTrailingZeros x ---- -- Note: The default implementation for this method is intentionally -- naive. However, the instances provided for the primitive integral -- types are implemented using CPU specific machine instructions. countTrailingZeros :: FiniteBits b => b -> Int -- | Default implementation for bit. -- -- Note that: bitDefault i = 1 shiftL i bitDefault :: (Bits a, Num a) => Int -> a -- | Default implementation for testBit. -- -- Note that: testBitDefault x i = (x .&. bit i) /= 0 testBitDefault :: (Bits a, Num a) => a -> Int -> Bool -- | Default implementation for popCount. -- -- This implementation is intentionally naive. Instances are expected to -- provide an optimized implementation for their size. popCountDefault :: (Bits a, Num a) => a -> Int -- | Attempt to convert an Integral type a to an -- Integral type b using the size of the types as -- measured by Bits methods. -- -- A simpler version of this function is: -- --
-- toIntegral :: (Integral a, Integral b) => a -> Maybe b -- toIntegral x -- | toInteger x == y = Just (fromInteger y) -- | otherwise = Nothing -- where -- y = toInteger x ---- -- This version requires going through Integer, which can be -- inefficient. However, toIntegralSized is optimized to allow -- GHC to statically determine the relative type sizes (as measured by -- bitSizeMaybe and isSigned) and avoid going through -- Integer for many types. (The implementation uses -- fromIntegral, which is itself optimized with rules for -- base types but may go through Integer for some type -- pairs.) toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b instance Data.Bits.FiniteBits GHC.Types.Bool instance Data.Bits.Bits GHC.Types.Int instance Data.Bits.FiniteBits GHC.Types.Int instance Data.Bits.Bits GHC.Types.Word instance Data.Bits.FiniteBits GHC.Types.Word instance Data.Bits.Bits GHC.Types.Bool instance Data.Bits.Bits GHC.Integer.Type.Integer instance Data.Bits.Bits GHC.Natural.Natural -- | 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. 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). -- --
-- >>> :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. -- --
-- >>> 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. isUpper :: Char -> Bool -- | Selects lower-case alphabetic Unicode characters (letters). isLower :: 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: -- --
-- >>> 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: -- --
-- >>> 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 wgencat :: Int -> Int instance GHC.Ix.Ix GHC.Unicode.GeneralCategory instance GHC.Enum.Bounded GHC.Unicode.GeneralCategory instance GHC.Enum.Enum GHC.Unicode.GeneralCategory instance GHC.Classes.Ord GHC.Unicode.GeneralCategory instance GHC.Classes.Eq GHC.Unicode.GeneralCategory instance GHC.Show.Show GHC.Unicode.GeneralCategory -- | 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 ressurrect the key, perhaps by -- storing it in the same data structure. -- -- The finalizer, and the relationship between the key and the value, -- exist regardless of whether the program keeps a reference to the -- Weak object or not. -- -- There may be multiple weak pointers with the same key. In this case, -- the finalizers for each of these weak pointers will all be run in some -- arbitrary order, or perhaps concurrently, when the key dies. If the -- programmer specifies a finalizer that assumes it has the only -- reference to an object (for example, a file that it wishes to close), -- then the programmer must ensure that there is only one such finalizer. -- -- If there are no other threads to run, the runtime system will check -- for runnable finalizers before declaring the system to be deadlocked. -- -- WARNING: weak pointers to ordinary non-primitive Haskell types are -- particularly fragile, because the compiler is free to optimise away or -- duplicate the underlying data structure. Therefore attempting to place -- a finalizer on an ordinary Haskell type may well result in the -- finalizer running earlier than you expected. This is not a problem for -- caches and memo tables where early finalization is benign. -- -- Finalizers can be used reliably for types that are created -- explicitly and have identity, such as IORef and -- MVar. However, to place a finalizer on one of these types, -- you should use the specific operation provided for that type, e.g. -- mkWeakIORef and addMVarFinalizer respectively (the -- non-uniformity is accidental). These operations attach the finalizer -- to the primitive object inside the box (e.g. MutVar# in the -- case of IORef), because attaching the finalizer to the box -- itself fails when the outer box is optimised away by the compiler. data Weak v 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 () runFinalizerBatch :: Int -> Array# (State# RealWorld -> State# RealWorld) -> IO () -- | 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 {-# CTYPE "HsWord8" #-} Word8 W8# :: Word# -> Word8 -- | 16-bit unsigned integer type data {-# CTYPE "HsWord16" #-} Word16 W16# :: Word# -> Word16 -- | 32-bit unsigned integer type data {-# CTYPE "HsWord32" #-} Word32 W32# :: Word# -> Word32 -- | 64-bit unsigned integer type data {-# CTYPE "HsWord64" #-} Word64 W64# :: Word# -> Word64 uncheckedShiftL64# :: Word# -> Int# -> Word# uncheckedShiftRL64# :: Word# -> Int# -> Word# -- | 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.Classes.Eq GHC.Word.Word64 instance GHC.Classes.Ord GHC.Word.Word64 instance GHC.Num.Num GHC.Word.Word64 instance GHC.Enum.Enum GHC.Word.Word64 instance GHC.Real.Integral GHC.Word.Word64 instance Data.Bits.Bits GHC.Word.Word64 instance Data.Bits.FiniteBits GHC.Word.Word64 instance GHC.Show.Show GHC.Word.Word64 instance GHC.Real.Real GHC.Word.Word64 instance GHC.Enum.Bounded GHC.Word.Word64 instance GHC.Ix.Ix GHC.Word.Word64 instance GHC.Classes.Eq GHC.Word.Word32 instance GHC.Classes.Ord GHC.Word.Word32 instance GHC.Num.Num GHC.Word.Word32 instance GHC.Enum.Enum GHC.Word.Word32 instance GHC.Real.Integral GHC.Word.Word32 instance Data.Bits.Bits GHC.Word.Word32 instance Data.Bits.FiniteBits GHC.Word.Word32 instance GHC.Show.Show GHC.Word.Word32 instance GHC.Real.Real GHC.Word.Word32 instance GHC.Enum.Bounded GHC.Word.Word32 instance GHC.Ix.Ix GHC.Word.Word32 instance GHC.Classes.Eq GHC.Word.Word16 instance GHC.Classes.Ord GHC.Word.Word16 instance GHC.Show.Show GHC.Word.Word16 instance GHC.Num.Num GHC.Word.Word16 instance GHC.Real.Real GHC.Word.Word16 instance GHC.Enum.Enum GHC.Word.Word16 instance GHC.Real.Integral GHC.Word.Word16 instance GHC.Enum.Bounded GHC.Word.Word16 instance GHC.Ix.Ix GHC.Word.Word16 instance Data.Bits.Bits GHC.Word.Word16 instance Data.Bits.FiniteBits GHC.Word.Word16 instance GHC.Classes.Eq GHC.Word.Word8 instance GHC.Classes.Ord GHC.Word.Word8 instance GHC.Show.Show GHC.Word.Word8 instance GHC.Num.Num GHC.Word.Word8 instance GHC.Real.Real GHC.Word.Word8 instance GHC.Enum.Enum GHC.Word.Word8 instance GHC.Real.Integral GHC.Word.Word8 instance GHC.Enum.Bounded GHC.Word.Word8 instance GHC.Ix.Ix GHC.Word.Word8 instance Data.Bits.Bits GHC.Word.Word8 instance Data.Bits.FiniteBits 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 rationalToFloat :: Integer -> Integer -> Float rationalToDouble :: Integer -> Integer -> Double -- | 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: -- --
-- floatToDigits base x = ([d1,d2,...,dn], e) ---- -- then -- --
n >= 1
x = 0.d1d2...dn * (base**e)
0 <= di <= base-1
-- >>> 2^100 :: Natural -- 1267650600228229401496703205376 ---- -- Operations whose result would be negative throw -- (Underflow :: ArithException), -- --
-- >>> -1 :: Natural -- *** Exception: arithmetic underflow --data 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.Functor Text.ParserCombinators.ReadP.P instance GHC.Base.Functor Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Applicative Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Monad Text.ParserCombinators.ReadP.ReadP instance Control.Monad.Fail.MonadFail Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Alternative Text.ParserCombinators.ReadP.ReadP instance GHC.Base.MonadPlus Text.ParserCombinators.ReadP.ReadP instance GHC.Base.Applicative Text.ParserCombinators.ReadP.P instance GHC.Base.MonadPlus Text.ParserCombinators.ReadP.P instance GHC.Base.Monad Text.ParserCombinators.ReadP.P instance Control.Monad.Fail.MonadFail Text.ParserCombinators.ReadP.P instance GHC.Base.Alternative Text.ParserCombinators.ReadP.P -- | This library defines parser combinators for precedence parsing. module Text.ParserCombinators.ReadPrec data ReadPrec a type Prec = Int minPrec :: Prec -- | Lift a precedence-insensitive ReadP to a ReadPrec. lift :: ReadP a -> ReadPrec a -- | (prec n p) checks whether the precedence context is less than -- or equal to n, and -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Read in Haskell 2010 is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readsPrec d r = readParen (d > app_prec) -- (\r -> [(Leaf m,t) | -- ("Leaf",s) <- lex r, -- (m,t) <- readsPrec (app_prec+1) s]) r -- -- ++ readParen (d > up_prec) -- (\r -> [(u:^:v,w) | -- (u,s) <- readsPrec (up_prec+1) r, -- (":^:",t) <- lex s, -- (v,w) <- readsPrec (up_prec+1) t]) r -- -- where app_prec = 10 -- up_prec = 5 ---- -- Note that right-associativity of :^: is unused. -- -- The derived instance in GHC is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readPrec = parens $ (prec app_prec $ do -- Ident "Leaf" <- lexP -- m <- step readPrec -- return (Leaf m)) -- -- +++ (prec up_prec $ do -- u <- step readPrec -- Symbol ":^:" <- lexP -- v <- step readPrec -- return (u :^: v)) -- -- where app_prec = 10 -- up_prec = 5 -- -- readListPrec = readListPrecDefault ---- -- Why do both readsPrec and readPrec exist, and why does -- GHC opt to implement readPrec in derived Read instances -- instead of readsPrec? The reason is that readsPrec is -- based on the ReadS type, and although ReadS is mentioned -- in the Haskell 2010 Report, it is not a very efficient parser data -- structure. -- -- readPrec, on the other hand, is based on a much more efficient -- ReadPrec datatype (a.k.a "new-style parsers"), but its -- definition relies on the use of the RankNTypes language -- extension. Therefore, readPrec (and its cousin, -- readListPrec) are marked as GHC-only. Nevertheless, it is -- recommended to use readPrec instead of readsPrec -- whenever possible for the efficiency improvements it brings. -- -- As mentioned above, derived Read instances in GHC will -- implement readPrec instead of readsPrec. The default -- implementations of readsPrec (and its cousin, readList) -- will simply use readPrec under the hood. If you are writing a -- Read instance by hand, it is recommended to write it like so: -- --
-- instance Read T where -- readPrec = ... -- readListPrec = readListPrecDefault --class Read a -- | attempts to parse a value from the front of the string, returning a -- list of (parsed value, remaining string) pairs. If there is no -- successful parse, the returned list is empty. -- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. readsPrec :: Read a => Int -> ReadS a -- | The method readList is provided to allow the programmer to give -- a specialised way of parsing lists of values. For example, this is -- used by the predefined Read instance of the Char type, -- where values of type String should be are expected to use -- double quotes, rather than square brackets. readList :: Read a => ReadS [a] -- | Proposed replacement for readsPrec using new-style parsers (GHC -- only). readPrec :: Read a => ReadPrec a -- | Proposed replacement for readList using new-style parsers (GHC -- only). The default definition uses readList. Instances that -- define readPrec should also define readListPrec as -- readListPrecDefault. readListPrec :: Read a => ReadPrec [a] -- | A parser for a type a, represented as a function that takes a -- String and returns a list of possible parses as -- (a,String) pairs. -- -- Note that this kind of backtracking parser is very inefficient; -- reading a large structure may be quite slow (cf ReadP). type ReadS a = String -> [(a, String)] -- | 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: -- --
-- 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.Read.Read GHC.Unicode.GeneralCategory instance GHC.Read.Read a => GHC.Read.Read (GHC.Base.NonEmpty a) instance GHC.Read.Read GHC.Types.Char instance GHC.Read.Read GHC.Types.Bool instance GHC.Read.Read GHC.Types.Ordering instance GHC.Read.Read a => GHC.Read.Read (GHC.Maybe.Maybe a) instance GHC.Read.Read a => GHC.Read.Read [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 Text.Read.Lex.Lexeme instance GHC.Read.Read GHC.Types.Int instance GHC.Read.Read GHC.Types.Word instance GHC.Read.Read GHC.Word.Word8 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.Integer.Type.Integer instance GHC.Read.Read GHC.Natural.Natural instance GHC.Read.Read GHC.Types.Float instance GHC.Read.Read GHC.Types.Double instance (GHC.Real.Integral a, GHC.Read.Read a) => GHC.Read.Read (GHC.Real.Ratio a) instance GHC.Read.Read () 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 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) -- | Odds and ends, mostly functions for reading and showing -- RealFloat-like kind of values. module Numeric -- | Converts a possibly-negative Real value to a string. showSigned :: Real a => (a -> ShowS) -> Int -> a -> ShowS -- | Shows a non-negative Integral number using the base -- specified by the first argument, and the character representation -- specified by the second. showIntAtBase :: (Integral a, Show a) => a -> (Int -> Char) -> a -> ShowS -- | Show non-negative Integral numbers in base 10. showInt :: Integral a => a -> ShowS -- | Show non-negative Integral numbers in base 16. showHex :: (Integral a, Show a) => a -> ShowS -- | Show non-negative Integral numbers in base 8. showOct :: (Integral a, Show a) => a -> ShowS -- | Show a signed RealFloat value using scientific (exponential) -- notation (e.g. 2.45e2, 1.5e-3). -- -- In the call showEFloat digs val, if digs is -- Nothing, the value is shown to full precision; if digs -- is Just d, then at most d digits after the -- decimal point are shown. showEFloat :: RealFloat a => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- (e.g. 245000, 0.0015). -- -- In the call showFFloat digs val, if digs is -- Nothing, the value is shown to full precision; if digs -- is Just d, then at most d digits after the -- decimal point are shown. showFFloat :: RealFloat a => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- for arguments whose absolute value lies between 0.1 and -- 9,999,999, and scientific notation otherwise. -- -- In the call showGFloat digs val, if digs is -- Nothing, the value is shown to full precision; if digs -- is Just d, then at most d digits after the -- decimal point are shown. showGFloat :: RealFloat a => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- (e.g. 245000, 0.0015). -- -- This behaves as showFFloat, except that a decimal point is -- always guaranteed, even if not needed. showFFloatAlt :: RealFloat a => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- for arguments whose absolute value lies between 0.1 and -- 9,999,999, and scientific notation otherwise. -- -- This behaves as showFFloat, except that a decimal point is -- always guaranteed, even if not needed. showGFloatAlt :: RealFloat a => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value to full precision using standard -- decimal notation for arguments whose absolute value lies between -- 0.1 and 9,999,999, and scientific notation -- otherwise. showFloat :: RealFloat a => a -> ShowS -- | 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 -- --
n >= 1
x = 0.d1d2...dn * (base**e)
0 <= di <= base-1
-- >>> 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. 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: -- --
-- 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.Ord (GHC.Ptr.Ptr a) instance GHC.Classes.Eq (GHC.Ptr.Ptr a) instance GHC.Classes.Ord (GHC.Ptr.FunPtr a) instance GHC.Classes.Eq (GHC.Ptr.FunPtr a) instance GHC.Show.Show (GHC.Ptr.FunPtr a) instance GHC.Show.Show (GHC.Ptr.Ptr a) -- | 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] module GHC.Fingerprint.Type data Fingerprint Fingerprint :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> Fingerprint instance GHC.Classes.Ord GHC.Fingerprint.Type.Fingerprint instance GHC.Classes.Eq GHC.Fingerprint.Type.Fingerprint instance GHC.Show.Show GHC.Fingerprint.Type.Fingerprint -- | 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 {-# CTYPE "HsInt8" #-} Int8 I8# :: Int# -> Int8 -- | 16-bit signed integer type data {-# CTYPE "HsInt16" #-} Int16 I16# :: Int# -> Int16 -- | 32-bit signed integer type data {-# CTYPE "HsInt32" #-} Int32 I32# :: Int# -> Int32 -- | 64-bit signed integer type data {-# CTYPE "HsInt64" #-} Int64 I64# :: Int# -> Int64 uncheckedIShiftL64# :: Int# -> Int# -> Int# uncheckedIShiftRA64# :: Int# -> Int# -> Int# 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.Classes.Eq GHC.Int.Int64 instance GHC.Classes.Ord GHC.Int.Int64 instance GHC.Show.Show GHC.Int.Int64 instance GHC.Num.Num GHC.Int.Int64 instance GHC.Enum.Enum GHC.Int.Int64 instance GHC.Real.Integral GHC.Int.Int64 instance GHC.Read.Read GHC.Int.Int64 instance Data.Bits.Bits GHC.Int.Int64 instance Data.Bits.FiniteBits GHC.Int.Int64 instance GHC.Real.Real GHC.Int.Int64 instance GHC.Enum.Bounded GHC.Int.Int64 instance GHC.Ix.Ix GHC.Int.Int64 instance GHC.Classes.Eq GHC.Int.Int32 instance GHC.Classes.Ord GHC.Int.Int32 instance GHC.Show.Show GHC.Int.Int32 instance GHC.Num.Num GHC.Int.Int32 instance GHC.Enum.Enum GHC.Int.Int32 instance GHC.Real.Integral GHC.Int.Int32 instance GHC.Read.Read GHC.Int.Int32 instance Data.Bits.Bits GHC.Int.Int32 instance Data.Bits.FiniteBits GHC.Int.Int32 instance GHC.Real.Real GHC.Int.Int32 instance GHC.Enum.Bounded GHC.Int.Int32 instance GHC.Ix.Ix GHC.Int.Int32 instance GHC.Classes.Eq GHC.Int.Int16 instance GHC.Classes.Ord GHC.Int.Int16 instance GHC.Show.Show GHC.Int.Int16 instance GHC.Num.Num GHC.Int.Int16 instance GHC.Real.Real GHC.Int.Int16 instance GHC.Enum.Enum GHC.Int.Int16 instance GHC.Real.Integral GHC.Int.Int16 instance GHC.Enum.Bounded GHC.Int.Int16 instance GHC.Ix.Ix GHC.Int.Int16 instance GHC.Read.Read GHC.Int.Int16 instance Data.Bits.Bits GHC.Int.Int16 instance Data.Bits.FiniteBits GHC.Int.Int16 instance GHC.Classes.Eq GHC.Int.Int8 instance GHC.Classes.Ord GHC.Int.Int8 instance GHC.Show.Show GHC.Int.Int8 instance GHC.Num.Num GHC.Int.Int8 instance GHC.Real.Real GHC.Int.Int8 instance GHC.Enum.Enum GHC.Int.Int8 instance GHC.Real.Integral GHC.Int.Int8 instance GHC.Enum.Bounded GHC.Int.Int8 instance GHC.Ix.Ix GHC.Int.Int8 instance GHC.Read.Read GHC.Int.Int8 instance Data.Bits.Bits GHC.Int.Int8 instance Data.Bits.FiniteBits 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 {-# CTYPE "HsInt8" #-} Int8 -- | 16-bit signed integer type data {-# CTYPE "HsInt16" #-} Int16 -- | 32-bit signed integer type data {-# CTYPE "HsInt32" #-} Int32 -- | 64-bit signed integer type data {-# CTYPE "HsInt64" #-} Int64 -- | The IOMode type module GHC.IO.IOMode -- | See openFile data IOMode ReadMode :: IOMode WriteMode :: IOMode AppendMode :: IOMode ReadWriteMode :: IOMode instance GHC.Show.Show GHC.IO.IOMode.IOMode instance GHC.Read.Read GHC.IO.IOMode.IOMode instance GHC.Enum.Enum GHC.IO.IOMode.IOMode instance GHC.Ix.Ix GHC.IO.IOMode.IOMode instance GHC.Classes.Ord GHC.IO.IOMode.IOMode instance GHC.Classes.Eq 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 {-# CTYPE "HsWord8" #-} Word8 -- | 16-bit unsigned integer type data {-# CTYPE "HsWord16" #-} Word16 -- | 32-bit unsigned integer type data {-# CTYPE "HsWord32" #-} Word32 -- | 64-bit unsigned integer type data {-# CTYPE "HsWord64" #-} Word64 -- | 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 -- | Propositional equality. If a :~: b is inhabited by some -- terminating value, then the type a is the same as the type -- b. To use this equality in practice, pattern-match on the -- a :~: b to get out the Refl constructor; in the body -- of the pattern-match, the compiler knows that a ~ b. data a :~: b [Refl] :: a :~: a 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. class a ~# b => (a :: k0) ~~ (b :: k1) -- | Kind heterogeneous propositional equality. Like :~:, a :~~: -- b is inhabited by a terminating value if and only if a -- is the same type as b. data a :~~: b [HRefl] :: a :~~: a infix 4 :~~: -- | Symmetry of equality sym :: (a :~: b) -> b :~: a -- | Transitivity of equality trans :: (a :~: b) -> (b :~: c) -> a :~: c -- | Type-safe cast, using propositional equality castWith :: (a :~: b) -> a -> b -- | Generalized form of type-safe cast using propositional equality gcastWith :: (a :~: b) -> (a ~ b => r) -> r -- | Apply one equality to another, respectively apply :: (f :~: g) -> (a :~: b) -> f a :~: g b -- | Extract equality of the arguments from an equality of applied types inner :: (f a :~: g b) -> a :~: b -- | Extract equality of type constructors from an equality of applied -- types outer :: (f a :~: g b) -> f :~: g -- | This class contains types where you can learn the equality of two -- types from information contained in terms. Typically, only -- singleton types should inhabit this class. class TestEquality f -- | Conditionally prove the equality of a and b. testEquality :: TestEquality f => f a -> f b -> Maybe (a :~: b) -- | A type family to compute Boolean equality. type family a == b infix 4 == instance forall k (a :: k) (b :: k). GHC.Classes.Eq (a Data.Type.Equality.:~: b) instance forall k (a :: k) (b :: k). GHC.Show.Show (a Data.Type.Equality.:~: b) instance forall k (a :: k) (b :: k). GHC.Classes.Ord (a Data.Type.Equality.:~: b) instance forall k (a :: k) (b :: k). (a GHC.Types.~ b) => GHC.Read.Read (a Data.Type.Equality.:~: b) 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). GHC.Classes.Eq (a Data.Type.Equality.:~~: b) instance forall k1 k2 (a :: k1) (b :: k2). GHC.Show.Show (a Data.Type.Equality.:~~: b) instance forall k1 k2 (a :: k1) (b :: k2). GHC.Classes.Ord (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 k1 k2 (a :: k1) (b :: k2). (a GHC.Types.~~ b) => GHC.Enum.Bounded (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) 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). (a GHC.Types.~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~: b) -- | Definition of representational equality (Coercion). module Data.Type.Coercion -- | Representational equality. If Coercion a b is inhabited by -- some terminating value, then the type a has the same -- underlying representation as the type b. -- -- To use this equality in practice, pattern-match on the Coercion a -- b to get out the Coercible a b instance, and then use -- coerce to apply it. data Coercion a b [Coercion] :: Coercible a b => Coercion a b -- | Type-safe cast, using representational equality coerceWith :: Coercion a b -> a -> b -- | Generalized form of type-safe cast using representational equality gcoerceWith :: Coercion a b -> (Coercible a b => r) -> r -- | Symmetry of representational equality sym :: Coercion a b -> Coercion b a -- | Transitivity of representational equality trans :: Coercion a b -> Coercion b c -> Coercion a c -- | Convert propositional (nominal) equality to representational equality repr :: (a :~: b) -> Coercion a b -- | This class contains types where you can learn the equality of two -- types from information contained in terms. Typically, only -- singleton types should inhabit this class. class TestCoercion f -- | Conditionally prove the representational equality of a and -- b. testCoercion :: TestCoercion f => f a -> f b -> Maybe (Coercion a b) instance forall k (a :: k) (b :: k). GHC.Classes.Eq (Data.Type.Coercion.Coercion a b) instance forall k (a :: k) (b :: k). GHC.Show.Show (Data.Type.Coercion.Coercion a b) instance forall k (a :: k) (b :: k). GHC.Classes.Ord (Data.Type.Coercion.Coercion a b) instance forall k (a :: k) (b :: k). GHC.Types.Coercible a b => GHC.Read.Read (Data.Type.Coercion.Coercion a b) instance forall k (a :: k) (b :: k). GHC.Types.Coercible a b => GHC.Enum.Bounded (Data.Type.Coercion.Coercion a b) instance forall k (a :: k). Data.Type.Coercion.TestCoercion ((Data.Type.Equality.:~:) a) instance forall 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) instance forall k (a :: k) (b :: k). GHC.Types.Coercible a b => GHC.Enum.Enum (Data.Type.Coercion.Coercion a b) module Control.Category -- | A class for categories. Instances should satisfy the laws -- --
-- >>> 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 Proxy :: Proxy t -- | asProxyTypeOf is a type-restricted version of const. It -- is usually used as an infix operator, and its typing forces its first -- argument (which is usually overloaded) to have the same type as the -- tag of the second. -- --
-- >>> 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 :: Type) KProxy :: KProxy t :: Type instance forall k (t :: k). GHC.Read.Read (Data.Proxy.Proxy t) instance forall k (t :: k). GHC.Enum.Bounded (Data.Proxy.Proxy t) instance forall k (s :: k). GHC.Classes.Eq (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Classes.Ord (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Show.Show (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Enum.Enum (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Ix.Ix (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Base.Semigroup (Data.Proxy.Proxy s) instance forall k (s :: k). GHC.Base.Monoid (Data.Proxy.Proxy s) instance GHC.Base.Functor Data.Proxy.Proxy instance GHC.Base.Applicative Data.Proxy.Proxy instance GHC.Base.Alternative Data.Proxy.Proxy instance GHC.Base.Monad Data.Proxy.Proxy instance GHC.Base.MonadPlus Data.Proxy.Proxy -- | 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"). -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ] -- -- >>> partitionEithers list -- (["foo","bar","baz"],[3,7]) ---- -- The pair returned by partitionEithers x should be the -- same pair as (lefts x, rights x): -- --
-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ] -- -- >>> partitionEithers list == (lefts list, rights list) -- True --partitionEithers :: [Either a b] -> ([a], [b]) instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Data.Either.Either a b) instance (GHC.Read.Read a, GHC.Read.Read b) => GHC.Read.Read (Data.Either.Either a b) instance (GHC.Classes.Ord a, GHC.Classes.Ord b) => GHC.Classes.Ord (Data.Either.Either a b) 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.Semigroup (Data.Either.Either a b) instance GHC.Base.Applicative (Data.Either.Either e) instance GHC.Base.Monad (Data.Either.Either e) -- | Converting strings to values. -- -- The Text.Read library is the canonical library to import for -- Read-class facilities. For GHC only, it offers an extended and -- much improved Read class, which constitutes a proposed -- alternative to the Haskell 2010 Read. In particular, writing -- parsers is easier, and the parsers are much more efficient. module Text.Read -- | Parsing of Strings, producing values. -- -- Derived instances of Read make the following assumptions, which -- derived instances of Show obey: -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Read in Haskell 2010 is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readsPrec d r = readParen (d > app_prec) -- (\r -> [(Leaf m,t) | -- ("Leaf",s) <- lex r, -- (m,t) <- readsPrec (app_prec+1) s]) r -- -- ++ readParen (d > up_prec) -- (\r -> [(u:^:v,w) | -- (u,s) <- readsPrec (up_prec+1) r, -- (":^:",t) <- lex s, -- (v,w) <- readsPrec (up_prec+1) t]) r -- -- where app_prec = 10 -- up_prec = 5 ---- -- Note that right-associativity of :^: is unused. -- -- The derived instance in GHC is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readPrec = parens $ (prec app_prec $ do -- Ident "Leaf" <- lexP -- m <- step readPrec -- return (Leaf m)) -- -- +++ (prec up_prec $ do -- u <- step readPrec -- Symbol ":^:" <- lexP -- v <- step readPrec -- return (u :^: v)) -- -- where app_prec = 10 -- up_prec = 5 -- -- readListPrec = readListPrecDefault ---- -- Why do both readsPrec and readPrec exist, and why does -- GHC opt to implement readPrec in derived Read instances -- instead of readsPrec? The reason is that readsPrec is -- based on the ReadS type, and although ReadS is mentioned -- in the Haskell 2010 Report, it is not a very efficient parser data -- structure. -- -- readPrec, on the other hand, is based on a much more efficient -- ReadPrec datatype (a.k.a "new-style parsers"), but its -- definition relies on the use of the RankNTypes language -- extension. Therefore, readPrec (and its cousin, -- readListPrec) are marked as GHC-only. Nevertheless, it is -- recommended to use readPrec instead of readsPrec -- whenever possible for the efficiency improvements it brings. -- -- As mentioned above, derived Read instances in GHC will -- implement readPrec instead of readsPrec. The default -- implementations of readsPrec (and its cousin, readList) -- will simply use readPrec under the hood. If you are writing a -- Read instance by hand, it is recommended to write it like so: -- --
-- instance Read T where -- readPrec = ... -- readListPrec = readListPrecDefault --class Read a -- | attempts to parse a value from the front of the string, returning a -- list of (parsed value, remaining string) pairs. If there is no -- successful parse, the returned list is empty. -- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. readsPrec :: Read a => Int -> ReadS a -- | The method readList is provided to allow the programmer to give -- a specialised way of parsing lists of values. For example, this is -- used by the predefined Read instance of the Char type, -- where values of type String should be are expected to use -- double quotes, rather than square brackets. readList :: Read a => ReadS [a] -- | Proposed replacement for readsPrec using new-style parsers (GHC -- only). readPrec :: Read a => ReadPrec a -- | Proposed replacement for readList using new-style parsers (GHC -- only). The default definition uses readList. Instances that -- define readPrec should also define readListPrec as -- readListPrecDefault. readListPrec :: Read a => ReadPrec [a] -- | A parser for a type a, represented as a function that takes a -- String and returns a list of possible parses as -- (a,String) pairs. -- -- Note that this kind of backtracking parser is very inefficient; -- reading a large structure may be quite slow (cf ReadP). type ReadS a = String -> [(a, String)] -- | equivalent to readsPrec with a precedence of 0. reads :: Read a => ReadS a -- | The read function reads input from a string, which must be -- completely consumed by the input process. read 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: -- --
-- >>> 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 is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. -- characters, see http://www.unicode.org/ for details). This set -- extends the ISO 8859-1 (Latin-1) character set (the first 256 -- characters), which is itself an extension of the ASCII character set -- (the first 128 characters). A character literal in Haskell has type -- Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char -- | Selects control characters, which are the non-printing characters of -- the Latin-1 subset of Unicode. isControl :: Char -> Bool -- | Returns True for any Unicode space character, and the control -- characters \t, \n, \r, \f, -- \v. isSpace :: Char -> Bool -- | Selects lower-case alphabetic Unicode characters (letters). isLower :: Char -> Bool -- | Selects upper-case or title-case alphabetic Unicode characters -- (letters). Title case is used by a small number of letter ligatures -- like the single-character form of Lj. isUpper :: Char -> Bool -- | Selects alphabetic Unicode characters (lower-case, upper-case and -- title-case letters, plus letters of caseless scripts and modifiers -- letters). This function is equivalent to isLetter. isAlpha :: Char -> Bool -- | Selects alphabetic or numeric 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: -- --
-- >>> 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: -- --
-- >>> 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: -- --
-- >>> 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: -- --
-- >>> 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: -- --
-- >>> 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: -- --
-- >>> 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 ): -- --
-- >>> 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). -- --
-- >>> :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. -- --
-- >>> 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'). -- --
-- >>> 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 -- | 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: -- --
-- 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, -- --
-- 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 -- | Coerce a value from one type to another, bypassing the type-checker. -- -- There are several legitimate ways to use unsafeCoerce: -- --
-- 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. -- --
-- -- 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.SomeSymbol instance GHC.Classes.Ord GHC.TypeLits.SomeSymbol instance GHC.Show.Show GHC.TypeLits.SomeSymbol instance GHC.Read.Read GHC.TypeLits.SomeSymbol -- | 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. -- -- A value of type StablePtr a is a stable pointer to a Haskell -- expression of type a. data {-# CTYPE "HsStablePtr" #-} 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 may -- not refer to an accessible memory location and any attempt to pass it -- to the member functions of the class Storable leads to -- undefined behaviour. castStablePtrToPtr :: StablePtr a -> Ptr () -- | The inverse of castStablePtrToPtr, i.e., we have the identity -- --
-- sp == castPtrToStablePtr (castStablePtrToPtr sp) ---- -- for any stable pointer sp on which freeStablePtr has -- not been executed yet. Moreover, castPtrToStablePtr may only be -- applied to pointers that have been produced by -- castStablePtrToPtr. castPtrToStablePtr :: Ptr () -> StablePtr a 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 value of the argument is not used. alignment :: Storable a => a -> Int -- | Read a value from a memory area regarded as an array of values of the -- same kind. The first argument specifies the start address of the array -- and the second the index into the array (the first element of the -- array has index 0). The following equality holds, -- --
-- peekElemOff addr idx = IOExts.fixIO $ \result -> -- peek (addr `plusPtr` (idx * sizeOf result)) ---- -- Note that this is only a specification, not necessarily the concrete -- implementation of the function. peekElemOff :: Storable a => Ptr a -> Int -> IO a -- | Write a value to a memory area regarded as an array of values of the -- same kind. The following equality holds: -- --
-- pokeElemOff addr idx x = -- poke (addr `plusPtr` (idx * sizeOf x)) x --pokeElemOff :: Storable a => Ptr a -> Int -> a -> IO () -- | Read a value from a memory location given by a base address and -- offset. The following equality holds: -- --
-- peekByteOff addr off = peek (addr `plusPtr` off) --peekByteOff :: Storable a => Ptr b -> Int -> IO a -- | Write a value to a memory location given by a base address and offset. -- The following equality holds: -- --
-- pokeByteOff addr off x = poke (addr `plusPtr` off) x --pokeByteOff :: Storable a => Ptr b -> Int -> a -> IO () -- | Read a value from the given memory location. -- -- Note that the peek and poke functions might require properly aligned -- addresses to function correctly. This is architecture dependent; thus, -- portable code should ensure that when peeking or poking values of some -- type a, the alignment constraint for a, as given by -- the function alignment is fulfilled. peek :: Storable a => Ptr a -> IO a -- | Write the given value to the given memory location. Alignment -- restrictions might apply; see peek. poke :: Storable a => Ptr a -> a -> IO () instance Foreign.Storable.Storable () instance Foreign.Storable.Storable GHC.Types.Bool instance Foreign.Storable.Storable GHC.Types.Char instance Foreign.Storable.Storable GHC.Types.Int instance Foreign.Storable.Storable GHC.Types.Word instance Foreign.Storable.Storable (GHC.Ptr.Ptr a) instance Foreign.Storable.Storable (GHC.Ptr.FunPtr a) instance Foreign.Storable.Storable (GHC.Stable.StablePtr a) instance Foreign.Storable.Storable GHC.Types.Float instance Foreign.Storable.Storable GHC.Types.Double instance Foreign.Storable.Storable GHC.Word.Word8 instance Foreign.Storable.Storable GHC.Word.Word16 instance Foreign.Storable.Storable GHC.Word.Word32 instance Foreign.Storable.Storable GHC.Word.Word64 instance Foreign.Storable.Storable GHC.Int.Int8 instance Foreign.Storable.Storable GHC.Int.Int16 instance Foreign.Storable.Storable GHC.Int.Int32 instance Foreign.Storable.Storable GHC.Int.Int64 instance (Foreign.Storable.Storable a, GHC.Real.Integral a) => Foreign.Storable.Storable (GHC.Real.Ratio a) instance Foreign.Storable.Storable GHC.Fingerprint.Type.Fingerprint -- | This module provides typed pointers to foreign data. It is part of the -- Foreign Function Interface (FFI) and will normally be imported via the -- Foreign module. module Foreign.Ptr -- | A value of type Ptr a represents a pointer to an -- object, or an array of objects, which may be marshalled to or from -- Haskell values of type a. -- -- The type a will often be an instance of class Storable -- which provides the marshalling operations. However this is not -- essential, and you can provide your own operations to access the -- pointer. For example you might write small foreign functions to get or -- set the fields of a C struct. data Ptr a -- | The constant nullPtr contains a distinguished value of -- Ptr that is not associated with a valid memory location. nullPtr :: Ptr a -- | The castPtr function casts a pointer from one type to another. castPtr :: Ptr a -> Ptr b -- | Advances the given address by the given offset in bytes. plusPtr :: Ptr a -> Int -> Ptr b -- | Given an arbitrary address and an alignment constraint, -- alignPtr yields the next higher address that fulfills the -- alignment constraint. An alignment constraint x is fulfilled -- by any address divisible by x. This operation is idempotent. alignPtr :: Ptr a -> Int -> Ptr a -- | Computes the offset required to get from the second to the first -- argument. We have -- --
-- p2 == p1 `plusPtr` (p2 `minusPtr` p1) --minusPtr :: Ptr a -> Ptr b -> Int -- | A value of type FunPtr a is a pointer to a function -- callable from foreign code. The type a will normally be a -- foreign type, a function type with zero or more arguments where -- --
-- foreign import ccall "stdlib.h &free" -- p_free :: FunPtr (Ptr a -> IO ()) ---- -- or a pointer to a Haskell function created using a wrapper stub -- declared to produce a FunPtr of the correct type. For example: -- --
-- type Compare = Int -> Int -> Bool -- foreign import ccall "wrapper" -- mkCompare :: Compare -> IO (FunPtr Compare) ---- -- Calls to wrapper stubs like mkCompare allocate storage, which -- should be released with freeHaskellFunPtr when no longer -- required. -- -- To convert FunPtr values to corresponding Haskell functions, -- one can define a dynamic stub for the specific foreign type, -- e.g. -- --
-- type IntFunction = CInt -> IO () -- foreign import ccall "dynamic" -- mkFun :: FunPtr IntFunction -> IntFunction --data FunPtr a -- | The constant nullFunPtr contains a distinguished value of -- FunPtr that is not associated with a valid memory location. nullFunPtr :: FunPtr a -- | Casts a FunPtr to a FunPtr of a different type. castFunPtr :: FunPtr a -> FunPtr b -- | Casts a FunPtr to a Ptr. -- -- Note: this is valid only on architectures where data and -- function pointers range over the same set of addresses, and should -- only be used for bindings to external libraries whose interface -- already relies on this assumption. castFunPtrToPtr :: FunPtr a -> Ptr b -- | Casts a Ptr to a FunPtr. -- -- Note: this is valid only on architectures where data and -- function pointers range over the same set of addresses, and should -- only be used for bindings to external libraries whose interface -- already relies on this assumption. castPtrToFunPtr :: Ptr a -> FunPtr b -- | Release the storage associated with the given FunPtr, which -- must have been obtained from a wrapper stub. This should be called -- whenever the return value from a foreign import wrapper function is no -- longer required; otherwise, the storage it uses will leak. freeHaskellFunPtr :: FunPtr a -> IO () -- | A signed integral type that can be losslessly converted to and from -- Ptr. This type is also compatible with the C99 type -- intptr_t, and can be marshalled to and from that type safely. newtype IntPtr IntPtr :: Int -> IntPtr -- | casts a Ptr to an IntPtr ptrToIntPtr :: Ptr a -> IntPtr -- | casts an IntPtr to a Ptr intPtrToPtr :: IntPtr -> Ptr a -- | An unsigned integral type that can be losslessly converted to and from -- Ptr. This type is also compatible with the C99 type -- uintptr_t, and can be marshalled to and from that type -- safely. newtype WordPtr WordPtr :: Word -> WordPtr -- | casts a Ptr to a WordPtr ptrToWordPtr :: Ptr a -> WordPtr -- | casts a WordPtr to a Ptr wordPtrToPtr :: WordPtr -> Ptr a instance GHC.Show.Show Foreign.Ptr.WordPtr instance GHC.Read.Read Foreign.Ptr.WordPtr instance Data.Bits.FiniteBits Foreign.Ptr.WordPtr instance Data.Bits.Bits Foreign.Ptr.WordPtr instance GHC.Real.Integral Foreign.Ptr.WordPtr instance GHC.Enum.Bounded Foreign.Ptr.WordPtr instance GHC.Real.Real Foreign.Ptr.WordPtr instance Foreign.Storable.Storable Foreign.Ptr.WordPtr instance GHC.Enum.Enum Foreign.Ptr.WordPtr instance GHC.Num.Num Foreign.Ptr.WordPtr instance GHC.Classes.Ord Foreign.Ptr.WordPtr instance GHC.Classes.Eq Foreign.Ptr.WordPtr instance GHC.Show.Show Foreign.Ptr.IntPtr instance GHC.Read.Read Foreign.Ptr.IntPtr instance Data.Bits.FiniteBits Foreign.Ptr.IntPtr instance Data.Bits.Bits Foreign.Ptr.IntPtr instance GHC.Real.Integral Foreign.Ptr.IntPtr instance GHC.Enum.Bounded Foreign.Ptr.IntPtr instance GHC.Real.Real Foreign.Ptr.IntPtr instance Foreign.Storable.Storable Foreign.Ptr.IntPtr instance GHC.Enum.Enum Foreign.Ptr.IntPtr instance GHC.Num.Num Foreign.Ptr.IntPtr instance GHC.Classes.Ord Foreign.Ptr.IntPtr instance GHC.Classes.Eq Foreign.Ptr.IntPtr -- | 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.) 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 {-# CTYPE "bool" #-} CBool CBool :: Word8 -> CBool newtype CIntPtr CIntPtr :: Int64 -> CIntPtr newtype CUIntPtr CUIntPtr :: Word64 -> CUIntPtr newtype CIntMax CIntMax :: Int64 -> CIntMax newtype CUIntMax CUIntMax :: Word64 -> CUIntMax -- | Haskell type representing the C clock_t type. (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.Show.Show Foreign.C.Types.CChar instance GHC.Read.Read Foreign.C.Types.CChar instance Data.Bits.FiniteBits Foreign.C.Types.CChar instance Data.Bits.Bits Foreign.C.Types.CChar instance GHC.Real.Integral Foreign.C.Types.CChar instance GHC.Enum.Bounded Foreign.C.Types.CChar instance GHC.Real.Real Foreign.C.Types.CChar instance Foreign.Storable.Storable Foreign.C.Types.CChar instance GHC.Enum.Enum Foreign.C.Types.CChar instance GHC.Num.Num Foreign.C.Types.CChar instance GHC.Classes.Ord Foreign.C.Types.CChar instance GHC.Classes.Eq Foreign.C.Types.CChar instance GHC.Show.Show Foreign.C.Types.CSChar instance GHC.Read.Read Foreign.C.Types.CSChar instance Data.Bits.FiniteBits Foreign.C.Types.CSChar instance Data.Bits.Bits Foreign.C.Types.CSChar instance GHC.Real.Integral Foreign.C.Types.CSChar instance GHC.Enum.Bounded Foreign.C.Types.CSChar instance GHC.Real.Real Foreign.C.Types.CSChar instance Foreign.Storable.Storable Foreign.C.Types.CSChar instance GHC.Enum.Enum Foreign.C.Types.CSChar instance GHC.Num.Num Foreign.C.Types.CSChar instance GHC.Classes.Ord Foreign.C.Types.CSChar instance GHC.Classes.Eq Foreign.C.Types.CSChar instance GHC.Show.Show Foreign.C.Types.CUChar instance GHC.Read.Read Foreign.C.Types.CUChar instance Data.Bits.FiniteBits Foreign.C.Types.CUChar instance Data.Bits.Bits Foreign.C.Types.CUChar instance GHC.Real.Integral Foreign.C.Types.CUChar instance GHC.Enum.Bounded Foreign.C.Types.CUChar instance GHC.Real.Real Foreign.C.Types.CUChar instance Foreign.Storable.Storable Foreign.C.Types.CUChar instance GHC.Enum.Enum Foreign.C.Types.CUChar instance GHC.Num.Num Foreign.C.Types.CUChar instance GHC.Classes.Ord Foreign.C.Types.CUChar instance GHC.Classes.Eq Foreign.C.Types.CUChar instance GHC.Show.Show Foreign.C.Types.CShort instance GHC.Read.Read Foreign.C.Types.CShort instance Data.Bits.FiniteBits Foreign.C.Types.CShort instance Data.Bits.Bits Foreign.C.Types.CShort instance GHC.Real.Integral Foreign.C.Types.CShort instance GHC.Enum.Bounded Foreign.C.Types.CShort instance GHC.Real.Real Foreign.C.Types.CShort instance Foreign.Storable.Storable Foreign.C.Types.CShort instance GHC.Enum.Enum Foreign.C.Types.CShort instance GHC.Num.Num Foreign.C.Types.CShort instance GHC.Classes.Ord Foreign.C.Types.CShort instance GHC.Classes.Eq Foreign.C.Types.CShort instance GHC.Show.Show Foreign.C.Types.CUShort instance GHC.Read.Read Foreign.C.Types.CUShort instance Data.Bits.FiniteBits Foreign.C.Types.CUShort instance Data.Bits.Bits Foreign.C.Types.CUShort instance GHC.Real.Integral Foreign.C.Types.CUShort instance GHC.Enum.Bounded Foreign.C.Types.CUShort instance GHC.Real.Real Foreign.C.Types.CUShort instance Foreign.Storable.Storable Foreign.C.Types.CUShort instance GHC.Enum.Enum Foreign.C.Types.CUShort instance GHC.Num.Num Foreign.C.Types.CUShort instance GHC.Classes.Ord Foreign.C.Types.CUShort instance GHC.Classes.Eq Foreign.C.Types.CUShort instance GHC.Show.Show Foreign.C.Types.CInt instance GHC.Read.Read Foreign.C.Types.CInt instance Data.Bits.FiniteBits Foreign.C.Types.CInt instance Data.Bits.Bits Foreign.C.Types.CInt instance GHC.Real.Integral Foreign.C.Types.CInt instance GHC.Enum.Bounded Foreign.C.Types.CInt instance GHC.Real.Real Foreign.C.Types.CInt instance Foreign.Storable.Storable Foreign.C.Types.CInt instance GHC.Enum.Enum Foreign.C.Types.CInt instance GHC.Num.Num Foreign.C.Types.CInt instance GHC.Classes.Ord Foreign.C.Types.CInt instance GHC.Classes.Eq Foreign.C.Types.CInt instance GHC.Show.Show Foreign.C.Types.CUInt instance GHC.Read.Read Foreign.C.Types.CUInt instance Data.Bits.FiniteBits Foreign.C.Types.CUInt instance Data.Bits.Bits Foreign.C.Types.CUInt instance GHC.Real.Integral Foreign.C.Types.CUInt instance GHC.Enum.Bounded Foreign.C.Types.CUInt instance GHC.Real.Real Foreign.C.Types.CUInt instance Foreign.Storable.Storable Foreign.C.Types.CUInt instance GHC.Enum.Enum Foreign.C.Types.CUInt instance GHC.Num.Num Foreign.C.Types.CUInt instance GHC.Classes.Ord Foreign.C.Types.CUInt instance GHC.Classes.Eq Foreign.C.Types.CUInt instance GHC.Show.Show Foreign.C.Types.CLong instance GHC.Read.Read Foreign.C.Types.CLong instance Data.Bits.FiniteBits Foreign.C.Types.CLong instance Data.Bits.Bits Foreign.C.Types.CLong instance GHC.Real.Integral Foreign.C.Types.CLong instance GHC.Enum.Bounded Foreign.C.Types.CLong instance GHC.Real.Real Foreign.C.Types.CLong instance Foreign.Storable.Storable Foreign.C.Types.CLong instance GHC.Enum.Enum Foreign.C.Types.CLong instance GHC.Num.Num Foreign.C.Types.CLong instance GHC.Classes.Ord Foreign.C.Types.CLong instance GHC.Classes.Eq Foreign.C.Types.CLong instance GHC.Show.Show Foreign.C.Types.CULong instance GHC.Read.Read Foreign.C.Types.CULong instance Data.Bits.FiniteBits Foreign.C.Types.CULong instance Data.Bits.Bits Foreign.C.Types.CULong instance GHC.Real.Integral Foreign.C.Types.CULong instance GHC.Enum.Bounded Foreign.C.Types.CULong instance GHC.Real.Real Foreign.C.Types.CULong instance Foreign.Storable.Storable Foreign.C.Types.CULong instance GHC.Enum.Enum Foreign.C.Types.CULong instance GHC.Num.Num Foreign.C.Types.CULong instance GHC.Classes.Ord Foreign.C.Types.CULong instance GHC.Classes.Eq Foreign.C.Types.CULong instance GHC.Show.Show Foreign.C.Types.CLLong instance GHC.Read.Read Foreign.C.Types.CLLong instance Data.Bits.FiniteBits Foreign.C.Types.CLLong instance Data.Bits.Bits Foreign.C.Types.CLLong instance GHC.Real.Integral Foreign.C.Types.CLLong instance GHC.Enum.Bounded Foreign.C.Types.CLLong instance GHC.Real.Real Foreign.C.Types.CLLong instance Foreign.Storable.Storable Foreign.C.Types.CLLong instance GHC.Enum.Enum Foreign.C.Types.CLLong instance GHC.Num.Num Foreign.C.Types.CLLong instance GHC.Classes.Ord Foreign.C.Types.CLLong instance GHC.Classes.Eq Foreign.C.Types.CLLong instance GHC.Show.Show Foreign.C.Types.CULLong instance GHC.Read.Read Foreign.C.Types.CULLong instance Data.Bits.FiniteBits Foreign.C.Types.CULLong instance Data.Bits.Bits Foreign.C.Types.CULLong instance GHC.Real.Integral Foreign.C.Types.CULLong instance GHC.Enum.Bounded Foreign.C.Types.CULLong instance GHC.Real.Real Foreign.C.Types.CULLong instance Foreign.Storable.Storable Foreign.C.Types.CULLong instance GHC.Enum.Enum Foreign.C.Types.CULLong instance GHC.Num.Num Foreign.C.Types.CULLong instance GHC.Classes.Ord Foreign.C.Types.CULLong instance GHC.Classes.Eq Foreign.C.Types.CULLong instance GHC.Show.Show Foreign.C.Types.CBool instance GHC.Read.Read Foreign.C.Types.CBool instance Data.Bits.FiniteBits Foreign.C.Types.CBool instance Data.Bits.Bits Foreign.C.Types.CBool instance GHC.Real.Integral Foreign.C.Types.CBool instance GHC.Enum.Bounded Foreign.C.Types.CBool instance GHC.Real.Real Foreign.C.Types.CBool instance Foreign.Storable.Storable Foreign.C.Types.CBool instance GHC.Enum.Enum Foreign.C.Types.CBool instance GHC.Num.Num Foreign.C.Types.CBool instance GHC.Classes.Ord Foreign.C.Types.CBool instance GHC.Classes.Eq Foreign.C.Types.CBool instance GHC.Show.Show Foreign.C.Types.CFloat instance GHC.Read.Read Foreign.C.Types.CFloat instance GHC.Float.RealFloat Foreign.C.Types.CFloat instance GHC.Real.RealFrac Foreign.C.Types.CFloat instance GHC.Float.Floating Foreign.C.Types.CFloat instance GHC.Real.Fractional Foreign.C.Types.CFloat instance GHC.Real.Real Foreign.C.Types.CFloat instance Foreign.Storable.Storable Foreign.C.Types.CFloat instance GHC.Enum.Enum Foreign.C.Types.CFloat instance GHC.Num.Num Foreign.C.Types.CFloat instance GHC.Classes.Ord Foreign.C.Types.CFloat instance GHC.Classes.Eq Foreign.C.Types.CFloat instance GHC.Show.Show Foreign.C.Types.CDouble instance GHC.Read.Read Foreign.C.Types.CDouble instance GHC.Float.RealFloat Foreign.C.Types.CDouble instance GHC.Real.RealFrac Foreign.C.Types.CDouble instance GHC.Float.Floating Foreign.C.Types.CDouble instance GHC.Real.Fractional Foreign.C.Types.CDouble instance GHC.Real.Real Foreign.C.Types.CDouble instance Foreign.Storable.Storable Foreign.C.Types.CDouble instance GHC.Enum.Enum Foreign.C.Types.CDouble instance GHC.Num.Num Foreign.C.Types.CDouble instance GHC.Classes.Ord Foreign.C.Types.CDouble instance GHC.Classes.Eq Foreign.C.Types.CDouble instance GHC.Show.Show Foreign.C.Types.CPtrdiff instance GHC.Read.Read Foreign.C.Types.CPtrdiff instance Data.Bits.FiniteBits Foreign.C.Types.CPtrdiff instance Data.Bits.Bits Foreign.C.Types.CPtrdiff instance GHC.Real.Integral Foreign.C.Types.CPtrdiff instance GHC.Enum.Bounded Foreign.C.Types.CPtrdiff instance GHC.Real.Real Foreign.C.Types.CPtrdiff instance Foreign.Storable.Storable Foreign.C.Types.CPtrdiff instance GHC.Enum.Enum Foreign.C.Types.CPtrdiff instance GHC.Num.Num Foreign.C.Types.CPtrdiff instance GHC.Classes.Ord Foreign.C.Types.CPtrdiff instance GHC.Classes.Eq Foreign.C.Types.CPtrdiff instance GHC.Show.Show Foreign.C.Types.CSize instance GHC.Read.Read Foreign.C.Types.CSize instance Data.Bits.FiniteBits Foreign.C.Types.CSize instance Data.Bits.Bits Foreign.C.Types.CSize instance GHC.Real.Integral Foreign.C.Types.CSize instance GHC.Enum.Bounded Foreign.C.Types.CSize instance GHC.Real.Real Foreign.C.Types.CSize instance Foreign.Storable.Storable Foreign.C.Types.CSize instance GHC.Enum.Enum Foreign.C.Types.CSize instance GHC.Num.Num Foreign.C.Types.CSize instance GHC.Classes.Ord Foreign.C.Types.CSize instance GHC.Classes.Eq Foreign.C.Types.CSize instance GHC.Show.Show Foreign.C.Types.CWchar instance GHC.Read.Read Foreign.C.Types.CWchar instance Data.Bits.FiniteBits Foreign.C.Types.CWchar instance Data.Bits.Bits Foreign.C.Types.CWchar instance GHC.Real.Integral Foreign.C.Types.CWchar instance GHC.Enum.Bounded Foreign.C.Types.CWchar instance GHC.Real.Real Foreign.C.Types.CWchar instance Foreign.Storable.Storable Foreign.C.Types.CWchar instance GHC.Enum.Enum Foreign.C.Types.CWchar instance GHC.Num.Num Foreign.C.Types.CWchar instance GHC.Classes.Ord Foreign.C.Types.CWchar instance GHC.Classes.Eq Foreign.C.Types.CWchar instance GHC.Show.Show Foreign.C.Types.CSigAtomic instance GHC.Read.Read Foreign.C.Types.CSigAtomic instance Data.Bits.FiniteBits Foreign.C.Types.CSigAtomic instance Data.Bits.Bits Foreign.C.Types.CSigAtomic instance GHC.Real.Integral Foreign.C.Types.CSigAtomic instance GHC.Enum.Bounded Foreign.C.Types.CSigAtomic instance GHC.Real.Real Foreign.C.Types.CSigAtomic instance Foreign.Storable.Storable Foreign.C.Types.CSigAtomic instance GHC.Enum.Enum Foreign.C.Types.CSigAtomic instance GHC.Num.Num Foreign.C.Types.CSigAtomic instance GHC.Classes.Ord Foreign.C.Types.CSigAtomic instance GHC.Classes.Eq Foreign.C.Types.CSigAtomic instance GHC.Show.Show Foreign.C.Types.CClock instance GHC.Read.Read Foreign.C.Types.CClock instance GHC.Real.Real Foreign.C.Types.CClock instance Foreign.Storable.Storable Foreign.C.Types.CClock instance GHC.Enum.Enum Foreign.C.Types.CClock instance GHC.Num.Num Foreign.C.Types.CClock instance GHC.Classes.Ord Foreign.C.Types.CClock instance GHC.Classes.Eq Foreign.C.Types.CClock instance GHC.Show.Show Foreign.C.Types.CTime instance GHC.Read.Read Foreign.C.Types.CTime instance GHC.Real.Real Foreign.C.Types.CTime instance Foreign.Storable.Storable Foreign.C.Types.CTime instance GHC.Enum.Enum Foreign.C.Types.CTime instance GHC.Num.Num Foreign.C.Types.CTime instance GHC.Classes.Ord Foreign.C.Types.CTime instance GHC.Classes.Eq Foreign.C.Types.CTime instance GHC.Show.Show Foreign.C.Types.CUSeconds instance GHC.Read.Read Foreign.C.Types.CUSeconds instance GHC.Real.Real Foreign.C.Types.CUSeconds instance Foreign.Storable.Storable Foreign.C.Types.CUSeconds instance GHC.Enum.Enum Foreign.C.Types.CUSeconds instance GHC.Num.Num Foreign.C.Types.CUSeconds instance GHC.Classes.Ord Foreign.C.Types.CUSeconds instance GHC.Classes.Eq Foreign.C.Types.CUSeconds instance GHC.Show.Show Foreign.C.Types.CSUSeconds instance GHC.Read.Read Foreign.C.Types.CSUSeconds instance GHC.Real.Real Foreign.C.Types.CSUSeconds instance Foreign.Storable.Storable Foreign.C.Types.CSUSeconds instance GHC.Enum.Enum Foreign.C.Types.CSUSeconds instance GHC.Num.Num Foreign.C.Types.CSUSeconds instance GHC.Classes.Ord Foreign.C.Types.CSUSeconds instance GHC.Classes.Eq Foreign.C.Types.CSUSeconds instance GHC.Show.Show Foreign.C.Types.CIntPtr instance GHC.Read.Read Foreign.C.Types.CIntPtr instance Data.Bits.FiniteBits Foreign.C.Types.CIntPtr instance Data.Bits.Bits Foreign.C.Types.CIntPtr instance GHC.Real.Integral Foreign.C.Types.CIntPtr instance GHC.Enum.Bounded Foreign.C.Types.CIntPtr instance GHC.Real.Real Foreign.C.Types.CIntPtr instance Foreign.Storable.Storable Foreign.C.Types.CIntPtr instance GHC.Enum.Enum Foreign.C.Types.CIntPtr instance GHC.Num.Num Foreign.C.Types.CIntPtr instance GHC.Classes.Ord Foreign.C.Types.CIntPtr instance GHC.Classes.Eq Foreign.C.Types.CIntPtr instance GHC.Show.Show Foreign.C.Types.CUIntPtr instance GHC.Read.Read Foreign.C.Types.CUIntPtr instance Data.Bits.FiniteBits Foreign.C.Types.CUIntPtr instance Data.Bits.Bits Foreign.C.Types.CUIntPtr instance GHC.Real.Integral Foreign.C.Types.CUIntPtr instance GHC.Enum.Bounded Foreign.C.Types.CUIntPtr instance GHC.Real.Real Foreign.C.Types.CUIntPtr instance Foreign.Storable.Storable Foreign.C.Types.CUIntPtr instance GHC.Enum.Enum Foreign.C.Types.CUIntPtr instance GHC.Num.Num Foreign.C.Types.CUIntPtr instance GHC.Classes.Ord Foreign.C.Types.CUIntPtr instance GHC.Classes.Eq Foreign.C.Types.CUIntPtr instance GHC.Show.Show Foreign.C.Types.CIntMax instance GHC.Read.Read Foreign.C.Types.CIntMax instance Data.Bits.FiniteBits Foreign.C.Types.CIntMax instance Data.Bits.Bits Foreign.C.Types.CIntMax instance GHC.Real.Integral Foreign.C.Types.CIntMax instance GHC.Enum.Bounded Foreign.C.Types.CIntMax instance GHC.Real.Real Foreign.C.Types.CIntMax instance Foreign.Storable.Storable Foreign.C.Types.CIntMax instance GHC.Enum.Enum Foreign.C.Types.CIntMax instance GHC.Num.Num Foreign.C.Types.CIntMax instance GHC.Classes.Ord Foreign.C.Types.CIntMax instance GHC.Classes.Eq Foreign.C.Types.CIntMax instance GHC.Show.Show Foreign.C.Types.CUIntMax instance GHC.Read.Read Foreign.C.Types.CUIntMax instance Data.Bits.FiniteBits Foreign.C.Types.CUIntMax instance Data.Bits.Bits Foreign.C.Types.CUIntMax instance GHC.Real.Integral Foreign.C.Types.CUIntMax instance GHC.Enum.Bounded Foreign.C.Types.CUIntMax instance GHC.Real.Real Foreign.C.Types.CUIntMax instance Foreign.Storable.Storable Foreign.C.Types.CUIntMax instance GHC.Enum.Enum Foreign.C.Types.CUIntMax instance GHC.Num.Num Foreign.C.Types.CUIntMax instance GHC.Classes.Ord Foreign.C.Types.CUIntMax instance GHC.Classes.Eq Foreign.C.Types.CUIntMax -- | 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. -- -- The Haskell Report defines no laws for Ord. However, -- <= is customarily expected to implement a non-strict partial -- order and have the following properties: -- --
-- comparing p x y = compare (p x) (p y) ---- -- Useful combinator for use in conjunction with the xxxBy -- family of functions from Data.List, for example: -- --
-- ... sortBy (comparing fst) ... --comparing :: Ord a => (b -> a) -> b -> b -> Ordering instance Foreign.Storable.Storable a => Foreign.Storable.Storable (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.Real.Real a => GHC.Real.Real (Data.Ord.Down a) instance GHC.Ix.Ix a => GHC.Ix.Ix (Data.Ord.Down a) instance GHC.Real.Integral a => GHC.Real.Integral (Data.Ord.Down a) instance GHC.Real.Fractional a => GHC.Real.Fractional (Data.Ord.Down a) instance GHC.Float.Floating a => GHC.Float.Floating (Data.Ord.Down a) instance Data.Bits.FiniteBits a => Data.Bits.FiniteBits (Data.Ord.Down a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Ord.Down a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Ord.Down a) instance Data.Bits.Bits a => Data.Bits.Bits (Data.Ord.Down a) instance GHC.Base.Monoid a => GHC.Base.Monoid (Data.Ord.Down a) instance GHC.Base.Semigroup a => GHC.Base.Semigroup (Data.Ord.Down a) instance GHC.Num.Num a => GHC.Num.Num (Data.Ord.Down a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Ord.Down a) instance GHC.Read.Read a => GHC.Read.Read (Data.Ord.Down a) instance GHC.Show.Show a => GHC.Show.Show (Data.Ord.Down a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Ord.Down a) instance GHC.Base.Functor Data.Ord.Down instance GHC.Base.Applicative Data.Ord.Down instance GHC.Base.Monad Data.Ord.Down -- | 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 :: Type) c (p :: k) K1 :: c -> K1 i :: Type c p :: k [unK1] :: K1 i :: Type c p :: k -> c -- | Meta-information (constructor names, etc.) newtype M1 (i :: Type) (c :: Meta) (f :: k -> Type) (p :: k) M1 :: f p -> M1 i :: Type c :: Meta f :: k -> Type p :: k [unM1] :: M1 i :: Type 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 :: Type) (p :: k) -- | Type synonym for URec Addr# type UAddr = URec (Ptr ()) -- | Type synonym for URec Char# type UChar = URec Char -- | Type synonym for URec Double# type UDouble = URec Double -- | Type synonym for URec Float# type UFloat = URec Float -- | Type synonym for URec Int# type UInt = URec Int -- | Type synonym for URec Word# type UWord = URec Word -- | Type synonym for encoding recursion (of kind Type) type Rec0 = K1 R -- | Tag for K1: recursion (of kind Type) data R -- | Type synonym for encoding meta-information for datatypes type D1 = M1 D -- | Type synonym for encoding meta-information for constructors type C1 = M1 C -- | Type synonym for encoding meta-information for record selectors type S1 = M1 S -- | Tag for M1: datatype data D -- | Tag for M1: constructor data C -- | Tag for M1: record selector data S -- | Class for datatypes that represent datatypes class Datatype d -- | The name of the datatype (unqualified) datatypeName :: Datatype d => t d f :: k -> Type a :: k -> [Char] -- | The fully-qualified name of the module where the type is declared moduleName :: Datatype d => t d f :: k -> Type a :: k -> [Char] -- | The package name of the module where the type is declared packageName :: Datatype d => t d f :: k -> Type a :: k -> [Char] -- | Marks if the datatype is actually a newtype isNewtype :: Datatype d => t d f :: k -> Type a :: k -> Bool -- | Class for datatypes that represent data constructors class Constructor c -- | The name of the constructor conName :: Constructor c => t c f :: k -> Type a :: k -> [Char] -- | The fixity of the constructor conFixity :: Constructor c => t c f :: k -> Type a :: k -> Fixity -- | Marks if this constructor is a record conIsRecord :: Constructor c => t c f :: k -> Type a :: k -> Bool -- | Class for datatypes that represent records class Selector s -- | The name of the selector selName :: Selector s => t s f :: k -> Type a :: k -> [Char] -- | The selector's unpackedness annotation (if any) selSourceUnpackedness :: Selector s => t s f :: k -> Type a :: k -> SourceUnpackedness -- | The selector's strictness annotation (if any) selSourceStrictness :: Selector s => t s f :: k -> Type a :: k -> SourceStrictness -- | The strictness that the compiler inferred for the selector selDecidedStrictness :: Selector s => t s f :: k -> Type a :: k -> DecidedStrictness -- | Datatype to represent the fixity of a constructor. An infix | -- declaration directly corresponds to an application of Infix. data Fixity Prefix :: Fixity Infix :: Associativity -> Int -> Fixity -- | This variant of Fixity appears at the type level. data FixityI PrefixI :: FixityI InfixI :: Associativity -> Nat -> FixityI -- | Datatype to represent the associativity of a constructor data Associativity LeftAssociative :: Associativity RightAssociative :: Associativity NotAssociative :: Associativity -- | Get the precedence of a fixity value. prec :: Fixity -> Int -- | The unpackedness of a field as the user wrote it in the source code. -- For example, in the following data type: -- --
-- data E = ExampleConstructor Int -- {-# NOUNPACK #-} Int -- {-# UNPACK #-} Int ---- -- The fields of ExampleConstructor have -- NoSourceUnpackedness, SourceNoUnpack, and -- SourceUnpack, respectively. data SourceUnpackedness NoSourceUnpackedness :: SourceUnpackedness SourceNoUnpack :: SourceUnpackedness SourceUnpack :: SourceUnpackedness -- | The strictness of a field as the user wrote it in the source code. For -- example, in the following data type: -- --
-- data E = ExampleConstructor Int ~Int !Int ---- -- The fields of ExampleConstructor have -- NoSourceStrictness, SourceLazy, and SourceStrict, -- respectively. data SourceStrictness NoSourceStrictness :: SourceStrictness SourceLazy :: SourceStrictness SourceStrict :: SourceStrictness -- | The strictness that GHC infers for a field during compilation. Whereas -- there are nine different combinations of SourceUnpackedness and -- SourceStrictness, the strictness that GHC decides will -- ultimately be one of lazy, strict, or unpacked. What GHC decides is -- affected both by what the user writes in the source code and by GHC -- flags. As an example, consider this data type: -- --
-- data E = ExampleConstructor {-# UNPACK #-} !Int !Int Int ---- --
-- from . to ≡ id -- to . from ≡ id --class Generic a where { -- | Generic representation type type family 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 . to1 ≡ id -- to1 . from1 ≡ id --class Generic1 (f :: k -> Type) where { -- | Generic representation type type family Rep1 f :: k -> Type; } -- | Convert from the datatype to its representation from1 :: Generic1 f => f a -> Rep1 f a -- | Convert from the representation to the datatype to1 :: Generic1 f => Rep1 f a -> f a instance GHC.Generics.Generic GHC.Generics.DecidedStrictness instance GHC.Ix.Ix GHC.Generics.DecidedStrictness instance GHC.Enum.Bounded GHC.Generics.DecidedStrictness instance GHC.Enum.Enum GHC.Generics.DecidedStrictness instance GHC.Read.Read GHC.Generics.DecidedStrictness instance GHC.Classes.Ord GHC.Generics.DecidedStrictness instance GHC.Show.Show GHC.Generics.DecidedStrictness instance GHC.Classes.Eq GHC.Generics.DecidedStrictness instance GHC.Generics.Generic GHC.Generics.SourceStrictness instance GHC.Ix.Ix GHC.Generics.SourceStrictness instance GHC.Enum.Bounded GHC.Generics.SourceStrictness instance GHC.Enum.Enum GHC.Generics.SourceStrictness instance GHC.Read.Read GHC.Generics.SourceStrictness instance GHC.Classes.Ord GHC.Generics.SourceStrictness instance GHC.Show.Show GHC.Generics.SourceStrictness instance GHC.Classes.Eq GHC.Generics.SourceStrictness instance GHC.Generics.Generic GHC.Generics.SourceUnpackedness instance GHC.Ix.Ix GHC.Generics.SourceUnpackedness instance GHC.Enum.Bounded GHC.Generics.SourceUnpackedness instance GHC.Enum.Enum GHC.Generics.SourceUnpackedness instance GHC.Read.Read GHC.Generics.SourceUnpackedness instance GHC.Classes.Ord GHC.Generics.SourceUnpackedness instance GHC.Show.Show GHC.Generics.SourceUnpackedness instance GHC.Classes.Eq GHC.Generics.SourceUnpackedness instance GHC.Generics.Generic GHC.Generics.Associativity instance GHC.Ix.Ix GHC.Generics.Associativity instance GHC.Enum.Bounded GHC.Generics.Associativity instance GHC.Enum.Enum GHC.Generics.Associativity instance GHC.Read.Read GHC.Generics.Associativity instance GHC.Classes.Ord GHC.Generics.Associativity instance GHC.Show.Show GHC.Generics.Associativity instance GHC.Classes.Eq GHC.Generics.Associativity instance GHC.Generics.Generic GHC.Generics.Fixity instance GHC.Read.Read GHC.Generics.Fixity instance GHC.Classes.Ord GHC.Generics.Fixity instance GHC.Show.Show GHC.Generics.Fixity instance GHC.Classes.Eq GHC.Generics.Fixity instance GHC.Generics.Generic1 (GHC.Generics.URec (GHC.Ptr.Ptr ())) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec (GHC.Ptr.Ptr ()) p) instance GHC.Base.Functor (GHC.Generics.URec (GHC.Ptr.Ptr ())) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec (GHC.Ptr.Ptr ()) p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec (GHC.Ptr.Ptr ()) p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Char) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Char p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Char) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Char p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Char p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Char p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Double) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Double p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Double) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Double p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Double p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Double p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Float) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Float p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Float) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Float p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Float p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Float p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Int) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Int p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Int) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Int p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Int p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Int p) instance GHC.Generics.Generic1 (GHC.Generics.URec GHC.Types.Word) instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.URec GHC.Types.Word p) instance GHC.Base.Functor (GHC.Generics.URec GHC.Types.Word) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.URec GHC.Types.Word p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.URec GHC.Types.Word p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.URec GHC.Types.Word p) instance forall (f :: * -> *) k (g :: k -> *). GHC.Base.Functor f => GHC.Generics.Generic1 (f GHC.Generics.:.: g) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Generics.Generic ((GHC.Generics.:.:) f g p) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (f GHC.Generics.:.: g) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Show.Show (f (g p)) => GHC.Show.Show ((GHC.Generics.:.:) f g p) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Read.Read (f (g p)) => GHC.Read.Read ((GHC.Generics.:.:) f g p) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Classes.Ord (f (g p)) => GHC.Classes.Ord ((GHC.Generics.:.:) f g p) instance forall k2 (f :: k2 -> *) k1 (g :: k1 -> k2) (p :: k1). GHC.Classes.Eq (f (g p)) => GHC.Classes.Eq ((GHC.Generics.:.:) f g p) instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (f GHC.Generics.:*: g) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). GHC.Generics.Generic ((GHC.Generics.:*:) f g p) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (f GHC.Generics.:*: g) 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.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.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.Eq (f p), GHC.Classes.Eq (g p)) => GHC.Classes.Eq ((GHC.Generics.:*:) f g p) instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (f GHC.Generics.:+: g) instance forall k (f :: k -> *) (g :: k -> *) (p :: k). GHC.Generics.Generic ((GHC.Generics.:+:) f g p) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (f GHC.Generics.:+: g) 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.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.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.Eq (f p), GHC.Classes.Eq (g p)) => GHC.Classes.Eq ((GHC.Generics.:+:) f g p) instance GHC.Generics.Generic1 (GHC.Generics.K1 i c) instance forall i c k (p :: k). GHC.Generics.Generic (GHC.Generics.K1 i c p) instance GHC.Base.Functor (GHC.Generics.K1 i c) instance forall i c k (p :: k). GHC.Show.Show c => GHC.Show.Show (GHC.Generics.K1 i c p) instance forall i c k (p :: k). GHC.Read.Read c => GHC.Read.Read (GHC.Generics.K1 i c p) instance forall i c k (p :: k). GHC.Classes.Ord c => GHC.Classes.Ord (GHC.Generics.K1 i c p) instance forall i c k (p :: k). GHC.Classes.Eq c => GHC.Classes.Eq (GHC.Generics.K1 i c p) instance forall k (f :: k -> *). GHC.Generics.Generic1 (GHC.Generics.Rec1 f) instance forall k (f :: k -> *) (p :: k). GHC.Generics.Generic (GHC.Generics.Rec1 f p) instance GHC.Base.Functor f => GHC.Base.Functor (GHC.Generics.Rec1 f) instance forall k (f :: k -> *) (p :: k). GHC.Show.Show (f p) => GHC.Show.Show (GHC.Generics.Rec1 f p) instance forall k (f :: k -> *) (p :: k). GHC.Read.Read (f p) => GHC.Read.Read (GHC.Generics.Rec1 f p) instance forall k (f :: k -> *) (p :: k). GHC.Classes.Ord (f p) => GHC.Classes.Ord (GHC.Generics.Rec1 f p) instance forall k (f :: k -> *) (p :: k). GHC.Classes.Eq (f p) => GHC.Classes.Eq (GHC.Generics.Rec1 f p) instance GHC.Generics.Generic1 GHC.Generics.Par1 instance GHC.Generics.Generic (GHC.Generics.Par1 p) instance GHC.Base.Functor GHC.Generics.Par1 instance GHC.Show.Show p => GHC.Show.Show (GHC.Generics.Par1 p) instance GHC.Read.Read p => GHC.Read.Read (GHC.Generics.Par1 p) instance GHC.Classes.Ord p => GHC.Classes.Ord (GHC.Generics.Par1 p) instance GHC.Classes.Eq p => GHC.Classes.Eq (GHC.Generics.Par1 p) instance GHC.Generics.Generic1 GHC.Generics.U1 instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.U1 p) instance GHC.Generics.Generic1 GHC.Generics.V1 instance forall k (p :: k). GHC.Generics.Generic (GHC.Generics.V1 p) instance GHC.Base.Functor GHC.Generics.V1 instance forall k (p :: k). GHC.Show.Show (GHC.Generics.V1 p) instance forall k (p :: k). GHC.Read.Read (GHC.Generics.V1 p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.V1 p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.V1 p) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *). GHC.Generics.Generic1 (GHC.Generics.M1 i c f) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Generics.Generic (GHC.Generics.M1 i c f p) instance GHC.Base.Functor f => GHC.Base.Functor (GHC.Generics.M1 i c f) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Show.Show (f p) => GHC.Show.Show (GHC.Generics.M1 i c f p) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Read.Read (f p) => GHC.Read.Read (GHC.Generics.M1 i c f p) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Classes.Ord (f p) => GHC.Classes.Ord (GHC.Generics.M1 i c f p) instance forall i (c :: GHC.Generics.Meta) k (f :: k -> *) (p :: k). GHC.Classes.Eq (f p) => GHC.Classes.Eq (GHC.Generics.M1 i c f p) instance forall k (p :: k). GHC.Read.Read (GHC.Generics.U1 p) instance GHC.Base.Semigroup p => GHC.Base.Semigroup (GHC.Generics.Par1 p) instance GHC.Base.Monoid p => GHC.Base.Monoid (GHC.Generics.Par1 p) instance GHC.Base.Applicative f => GHC.Base.Applicative (GHC.Generics.Rec1 f) instance GHC.Base.Alternative f => GHC.Base.Alternative (GHC.Generics.Rec1 f) instance GHC.Base.MonadPlus f => GHC.Base.MonadPlus (GHC.Generics.Rec1 f) instance forall k (f :: k -> *) (p :: k). GHC.Base.Semigroup (f p) => GHC.Base.Semigroup (GHC.Generics.Rec1 f p) instance forall k (f :: k -> *) (p :: k). GHC.Base.Monoid (f p) => GHC.Base.Monoid (GHC.Generics.Rec1 f p) instance forall k c i (p :: k). GHC.Base.Semigroup c => GHC.Base.Semigroup (GHC.Generics.K1 i c p) instance forall k c i (p :: k). GHC.Base.Monoid c => GHC.Base.Monoid (GHC.Generics.K1 i c p) instance GHC.Base.Applicative f => GHC.Base.Applicative (GHC.Generics.M1 i c f) instance GHC.Base.Alternative f => GHC.Base.Alternative (GHC.Generics.M1 i c f) instance GHC.Base.Monad f => GHC.Base.Monad (GHC.Generics.M1 i c f) instance GHC.Base.MonadPlus f => GHC.Base.MonadPlus (GHC.Generics.M1 i c f) instance 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 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 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 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] instance GHC.Generics.Generic (GHC.Base.NonEmpty a) instance GHC.Generics.Generic (GHC.Maybe.Maybe a) instance GHC.Generics.Generic (Data.Either.Either a b) instance GHC.Generics.Generic GHC.Types.Bool instance GHC.Generics.Generic GHC.Types.Ordering instance forall k (t :: k). GHC.Generics.Generic (Data.Proxy.Proxy t) instance GHC.Generics.Generic () instance GHC.Generics.Generic (a, b) instance GHC.Generics.Generic (a, b, c) instance GHC.Generics.Generic (a, b, c, d) instance GHC.Generics.Generic (a, b, c, d, e) instance GHC.Generics.Generic (a, b, c, d, e, f) instance GHC.Generics.Generic (a, b, c, d, e, f, g) instance GHC.Generics.Generic (Data.Ord.Down a) instance GHC.Generics.Generic GHC.Stack.Types.SrcLoc instance GHC.Generics.Generic GHC.Unicode.GeneralCategory instance GHC.Generics.Generic GHC.Fingerprint.Type.Fingerprint instance GHC.Generics.Generic1 [] instance GHC.Generics.Generic1 GHC.Base.NonEmpty instance GHC.Generics.Generic1 GHC.Maybe.Maybe instance GHC.Generics.Generic1 (Data.Either.Either a) instance GHC.Generics.Generic1 Data.Proxy.Proxy instance GHC.Generics.Generic1 ((,) a) instance GHC.Generics.Generic1 ((,,) a b) instance GHC.Generics.Generic1 ((,,,) a b c) instance GHC.Generics.Generic1 ((,,,,) a b c d) instance GHC.Generics.Generic1 ((,,,,,) a b c d e) instance GHC.Generics.Generic1 ((,,,,,,) a b c d e f) instance GHC.Generics.Generic1 Data.Ord.Down instance (GHC.TypeLits.KnownSymbol n, GHC.TypeLits.KnownSymbol m, GHC.TypeLits.KnownSymbol p, GHC.Generics.SingI nt) => GHC.Generics.Datatype ('GHC.Generics.MetaData n m p nt) instance (GHC.TypeLits.KnownSymbol n, GHC.Generics.SingI f, GHC.Generics.SingI r) => GHC.Generics.Constructor ('GHC.Generics.MetaCons n f r) instance (GHC.Generics.SingI mn, GHC.Generics.SingI su, GHC.Generics.SingI ss, GHC.Generics.SingI ds) => GHC.Generics.Selector ('GHC.Generics.MetaSel mn su ss ds) instance GHC.Generics.SingKind GHC.Types.Symbol instance GHC.Generics.SingKind GHC.Types.Bool instance GHC.Generics.SingKind a => GHC.Generics.SingKind (GHC.Maybe.Maybe a) instance GHC.Generics.SingKind GHC.Generics.FixityI instance GHC.Generics.SingKind GHC.Generics.Associativity instance GHC.Generics.SingKind GHC.Generics.SourceUnpackedness instance GHC.Generics.SingKind GHC.Generics.SourceStrictness instance GHC.Generics.SingKind GHC.Generics.DecidedStrictness instance GHC.TypeLits.KnownSymbol a => GHC.Generics.SingI a instance GHC.Generics.SingI 'GHC.Types.True instance GHC.Generics.SingI 'GHC.Types.False instance GHC.Generics.SingI 'GHC.Maybe.Nothing instance forall a1 (a2 :: a1). GHC.Generics.SingI a2 => GHC.Generics.SingI ('GHC.Maybe.Just a2) instance GHC.Generics.SingI 'GHC.Generics.PrefixI instance (GHC.Generics.SingI a, GHC.TypeNats.KnownNat n) => GHC.Generics.SingI ('GHC.Generics.InfixI a n) instance GHC.Generics.SingI 'GHC.Generics.LeftAssociative instance GHC.Generics.SingI 'GHC.Generics.RightAssociative instance GHC.Generics.SingI 'GHC.Generics.NotAssociative instance GHC.Generics.SingI 'GHC.Generics.NoSourceUnpackedness instance GHC.Generics.SingI 'GHC.Generics.SourceNoUnpack instance GHC.Generics.SingI 'GHC.Generics.SourceUnpack instance GHC.Generics.SingI 'GHC.Generics.NoSourceStrictness instance GHC.Generics.SingI 'GHC.Generics.SourceLazy instance GHC.Generics.SingI 'GHC.Generics.SourceStrict instance GHC.Generics.SingI 'GHC.Generics.DecidedLazy instance GHC.Generics.SingI 'GHC.Generics.DecidedStrict instance GHC.Generics.SingI 'GHC.Generics.DecidedUnpack instance forall k (p :: k). GHC.Base.Semigroup (GHC.Generics.V1 p) instance forall k (p :: k). GHC.Classes.Eq (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Classes.Ord (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Show.Show (GHC.Generics.U1 p) instance GHC.Base.Functor GHC.Generics.U1 instance GHC.Base.Applicative GHC.Generics.U1 instance GHC.Base.Alternative GHC.Generics.U1 instance GHC.Base.Monad GHC.Generics.U1 instance GHC.Base.MonadPlus GHC.Generics.U1 instance forall k (p :: k). GHC.Base.Semigroup (GHC.Generics.U1 p) instance forall k (p :: k). GHC.Base.Monoid (GHC.Generics.U1 p) instance GHC.Base.Applicative GHC.Generics.Par1 instance GHC.Base.Monad GHC.Generics.Par1 instance GHC.Base.Monad f => GHC.Base.Monad (GHC.Generics.Rec1 f) instance GHC.Base.Monoid c => GHC.Base.Applicative (GHC.Generics.K1 i c) instance (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (f GHC.Generics.:*: g) instance (GHC.Base.Alternative f, GHC.Base.Alternative g) => GHC.Base.Alternative (f GHC.Generics.:*: g) instance (GHC.Base.Monad f, GHC.Base.Monad g) => GHC.Base.Monad (f GHC.Generics.:*: g) instance (GHC.Base.MonadPlus f, GHC.Base.MonadPlus g) => GHC.Base.MonadPlus (f GHC.Generics.:*: g) instance 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 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 (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (f GHC.Generics.:.: g) instance (GHC.Base.Alternative f, GHC.Base.Applicative g) => GHC.Base.Alternative (f GHC.Generics.:.: g) -- | A 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. -- --
-- >>> mempty :: Sum Int -- Sum 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: -- --
-- >>> "Hello world" <> mempty -- "Hello world" --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. -- --
-- >>> [1,2,3] <> [4,5,6] -- [1,2,3,4,5,6] --(<>) :: Semigroup a => a -> a -> a infixr 6 <> -- | The dual of a Monoid, obtained by swapping the arguments of -- mappend. -- --
-- >>> getDual (mappend (Dual "Hello") (Dual "World")) -- "WorldHello" --newtype Dual a Dual :: a -> Dual a [getDual] :: Dual a -> a -- | The monoid of endomorphisms under composition. -- --
-- >>> let computation = Endo ("Hello, " ++) <> Endo (++ "!") -- -- >>> appEndo computation "Haskell" -- "Hello, Haskell!" --newtype Endo a Endo :: (a -> a) -> Endo a [appEndo] :: Endo a -> a -> a -- | Boolean monoid under conjunction (&&). -- --
-- >>> getAll (All True <> mempty <> All False) -- False ---- --
-- >>> getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8])) -- False --newtype All All :: Bool -> All [getAll] :: All -> Bool -- | Boolean monoid under disjunction (||). -- --
-- >>> getAny (Any True <> mempty <> Any False) -- True ---- --
-- >>> getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8])) -- True --newtype Any Any :: Bool -> Any [getAny] :: Any -> Bool -- | Monoid under addition. -- --
-- >>> getSum (Sum 1 <> Sum 2 <> mempty) -- 3 --newtype Sum a Sum :: a -> Sum a [getSum] :: Sum a -> a -- | Monoid under multiplication. -- --
-- >>> getProduct (Product 3 <> Product 4 <> mempty) -- 12 --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. -- --
-- >>> getFirst (First (Just "hello") <> First Nothing <> First (Just "world")) -- Just "hello" ---- -- Use of this type is discouraged. Note the following equivalence: -- --
-- Data.Monoid.First x === Maybe (Data.Semigroup.First x) ---- -- In addition to being equivalent in the structural sense, the two also -- have Monoid instances that behave the same. This type will be -- marked deprecated in GHC 8.8, and removed in GHC 8.10. Users are -- advised to use the variant from Data.Semigroup and wrap it in -- Maybe. 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) -- --
-- >>> getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world")) -- Just "world" ---- -- Use of this type is discouraged. Note the following equivalence: -- --
-- Data.Monoid.Last x === Maybe (Data.Semigroup.Last x) ---- -- In addition to being equivalent in the structural sense, the two also -- have Monoid instances that behave the same. This type will be -- marked deprecated in GHC 8.8, and removed in GHC 8.10. Users are -- advised to use the variant from Data.Semigroup and wrap it in -- Maybe. newtype Last a Last :: Maybe a -> Last a [getLast] :: Last a -> Maybe a -- | Monoid under <|>. -- --
-- >>> getAlt (Alt (Just 12) <> Alt (Just 24)) -- Just 12 ---- --
-- >>> getAlt $ Alt Nothing <> Alt (Just 24) -- Just 24 --newtype Alt f a Alt :: f a -> Alt f a [getAlt] :: Alt f a -> f a -- | This data type witnesses the lifting of a Monoid into an -- Applicative pointwise. newtype Ap f a Ap :: f a -> Ap f a [getAp] :: Ap f a -> f a instance GHC.Base.Monad Data.Monoid.First instance GHC.Base.Applicative Data.Monoid.First instance GHC.Base.Functor Data.Monoid.First instance GHC.Generics.Generic1 Data.Monoid.First instance GHC.Generics.Generic (Data.Monoid.First a) instance GHC.Show.Show a => GHC.Show.Show (Data.Monoid.First a) instance GHC.Read.Read a => GHC.Read.Read (Data.Monoid.First a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Monoid.First a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Monoid.First a) instance GHC.Base.Monad Data.Monoid.Last instance GHC.Base.Applicative Data.Monoid.Last instance GHC.Base.Functor Data.Monoid.Last instance GHC.Generics.Generic1 Data.Monoid.Last instance GHC.Generics.Generic (Data.Monoid.Last a) instance GHC.Show.Show a => GHC.Show.Show (Data.Monoid.Last a) instance GHC.Read.Read a => GHC.Read.Read (Data.Monoid.Last a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Monoid.Last a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Monoid.Last a) instance forall k (f :: k -> *) (a :: k). GHC.Show.Show (f a) => GHC.Show.Show (Data.Monoid.Ap f a) instance forall k (f :: k -> *) (a :: k). GHC.Read.Read (f a) => GHC.Read.Read (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.Base.MonadPlus f => GHC.Base.MonadPlus (Data.Monoid.Ap f) 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 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.Base.Functor f => GHC.Base.Functor (Data.Monoid.Ap f) instance forall k (f :: k -> *) (a :: k). GHC.Classes.Eq (f a) => GHC.Classes.Eq (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 GHC.Base.Applicative f => GHC.Base.Applicative (Data.Monoid.Ap f) instance GHC.Base.Alternative f => GHC.Base.Alternative (Data.Monoid.Ap f) instance (GHC.Base.Applicative f, GHC.Base.Semigroup a) => GHC.Base.Semigroup (Data.Monoid.Ap f a) instance (GHC.Base.Applicative f, GHC.Base.Monoid a) => GHC.Base.Monoid (Data.Monoid.Ap f a) instance (GHC.Base.Applicative f, GHC.Enum.Bounded a) => GHC.Enum.Bounded (Data.Monoid.Ap f a) instance (GHC.Base.Applicative f, GHC.Num.Num a) => GHC.Num.Num (Data.Monoid.Ap f a) instance GHC.Base.Semigroup (Data.Monoid.Last a) instance GHC.Base.Monoid (Data.Monoid.Last a) instance GHC.Base.Semigroup (Data.Monoid.First a) instance GHC.Base.Monoid (Data.Monoid.First 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 -- | Append two lists, i.e., -- --
-- [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] -- [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...] ---- -- If the first list is not finite, the result is the first list. (++) :: [a] -> [a] -> [a] infixr 5 ++ -- | <math>. Extract the first element of a list, which must be -- non-empty. -- --
-- >>> head [1, 2, 3] -- 1 -- -- >>> head [1..] -- 1 -- -- >>> head [] -- Exception: Prelude.head: empty list --head :: [a] -> a -- | <math>. Extract the last element of a list, which must be finite -- and non-empty. -- --
-- >>> last [1, 2, 3] -- 3 -- -- >>> last [1..] -- * Hangs forever * -- -- >>> last [] -- Exception: Prelude.last: empty list --last :: [a] -> a -- | <math>. Extract the elements after the head of a list, which -- must be non-empty. -- --
-- >>> tail [1, 2, 3] -- [2,3] -- -- >>> tail [1] -- [] -- -- >>> tail [] -- Exception: Prelude.tail: empty list --tail :: [a] -> [a] -- | <math>. Return all the elements of a list except the last one. -- The list must be non-empty. -- --
-- >>> init [1, 2, 3] -- [1,2] -- -- >>> init [1] -- [] -- -- >>> init [] -- Exception: Prelude.init: empty list --init :: [a] -> [a] -- | <math>. Decompose a list into its head and tail. -- --
-- >>> uncons [] -- Nothing -- -- >>> uncons [1] -- Just (1,[]) -- -- >>> uncons [1, 2, 3] -- Just (1,[2,3]) --uncons :: [a] -> Maybe (a, [a]) -- | Produce singleton list. -- --
-- >>> singleton True -- [True] --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, ...] ---- --
-- >>> map (+1) [1, 2, 3] -- [2,3,4] --map :: (a -> b) -> [a] -> [b] -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. -- --
-- >>> 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. -- For example, -- --
-- >>> intersperse ',' "abcde" -- "a,b,c,d,e" --intersperse :: a -> [a] -> [a] -- | intercalate xs xss is equivalent to (concat -- (intersperse xs xss)). It inserts the list xs in -- between the lists in xss and concatenates the result. -- --
-- >>> intercalate ", " ["Lorem", "ipsum", "dolor"] -- "Lorem, ipsum, dolor" --intercalate :: [a] -> [[a]] -> [a] -- | The transpose function transposes the rows and columns of its -- argument. For example, -- --
-- >>> transpose [[1,2,3],[4,5,6]] -- [[1,4],[2,5],[3,6]] ---- -- If some of the rows are shorter than the following rows, their -- elements are skipped: -- --
-- >>> transpose [[10,11],[20],[],[30,31,32]] -- [[10,20,30],[11,31],[32]] --transpose :: [[a]] -> [[a]] -- | The subsequences function returns the list of all subsequences -- of the argument. -- --
-- >>> subsequences "abc" -- ["","a","b","ab","c","ac","bc","abc"] --subsequences :: [a] -> [[a]] -- | The permutations function returns the list of all permutations -- of the argument. -- --
-- >>> permutations "abc" -- ["abc","bac","cba","bca","cab","acb"] --permutations :: [a] -> [[a]] -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a list, reduces the -- list using the binary operator, from left to right: -- --
-- foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn ---- -- The list must be finite. -- --
-- >>> foldl (+) 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 :: (a -> a -> a) -> [a] -> a -- | A strict version of foldl1. foldl1' :: (a -> a -> a) -> [a] -> a -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a list, reduces -- the list using the binary operator, from right to left: -- --
-- foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) --foldr :: (a -> b -> b) -> b -> [a] -> b -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty lists. 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 -- -- >>> foldr1 (+) [1..] -- * Hangs forever * --foldr1 :: (a -> a -> a) -> [a] -> a -- | Concatenate a list of lists. -- --
-- >>> concat [] -- [] -- -- >>> concat [[42]] -- [42] -- -- >>> concat [[1,2,3], [4,5], [6], []] -- [1,2,3,4,5,6] --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 ---- --
-- >>> concatMap (\i -> [-i,i]) [] -- [] -- -- >>> concatMap (\i -> [-i,i]) [1,2,3] -- [-1,1,-2,2,-3,3] --concatMap :: (a -> [b]) -> [a] -> [b] -- | and returns the conjunction of a Boolean list. For the result -- to be True, the list must be finite; False, however, -- results from a False value at a finite index of a finite or -- infinite list. -- --
-- >>> and [] -- 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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 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 => [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 => [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 ---- --
-- >>> 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"] -- -- >>> scanl (+) 0 [1..] -- * Hangs forever * --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, ...] ---- --
-- >>> 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] -- -- >>> scanl1 (+) [1..] -- * Hangs forever * --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. ---- --
-- >>> 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"] -- -- >>> scanr (+) 0 [1..] -- * Hangs forever * --scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | <math>. scanr1 is a variant of scanr that has no -- starting value argument. -- --
-- >>> 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] -- -- >>> scanr1 (+) [1..] -- * Hangs forever * --scanr1 :: (a -> a -> a) -> [a] -> [a] -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a list, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new list. mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a list, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new list. mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) -- | iterate f x returns an infinite list of repeated -- applications of f to x: -- --
-- iterate f x == [x, f x, f (f x), ...] ---- -- 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. -- --
-- >>> iterate not True -- [True,False,True,False... -- -- >>> iterate (+3) 42 -- [42,45,48,51,54,57,60,63... --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. iterate' :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. -- --
-- >>> repeat 17 -- [17,17,17,17,17,17,17,17,17... --repeat :: a -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. -- --
-- >>> replicate 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. -- --
-- >>> cycle [] -- Exception: Prelude.cycle: empty list -- -- >>> cycle [42] -- [42,42,42,42,42,42,42,42,42,42... -- -- >>> cycle [2, 5, 7] -- [2,5,7,2,5,7,2,5,7,2,5,7... --cycle :: [a] -> [a] -- | The unfoldr function is a `dual' to foldr: while -- foldr reduces a list to a summary value, unfoldr builds -- a list from a seed value. The function takes the element and returns -- Nothing if it is done producing the list or returns Just -- (a,b), in which case, a is a prepended to the list -- and b is used as the next element in a recursive call. For -- example, -- --
-- iterate f == unfoldr (\x -> Just (x, f x)) ---- -- In some cases, unfoldr can undo a foldr operation: -- --
-- unfoldr f' (foldr f z xs) == xs ---- -- if the following holds: -- --
-- f' (f x y) = Just (x,y) -- f' z = Nothing ---- -- A simple use of unfoldr: -- --
-- >>> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10 -- [10,9,8,7,6,5,4,3,2,1] --unfoldr :: (b -> Maybe (a, b)) -> b -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n > length xs. -- --
-- >>> take 5 "Hello World!" -- "Hello" -- -- >>> take 3 [1,2,3,4,5] -- [1,2,3] -- -- >>> take 3 [1,2] -- [1,2] -- -- >>> take 3 [] -- [] -- -- >>> take (-1) [1,2] -- [] -- -- >>> take 0 [1,2] -- [] ---- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. take :: Int -> [a] -> [a] -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n > length -- xs. -- --
-- >>> drop 6 "Hello World!" -- "World!" -- -- >>> drop 3 [1,2,3,4,5] -- [4,5] -- -- >>> drop 3 [1,2] -- [] -- -- >>> drop 3 [] -- [] -- -- >>> drop (-1) [1,2] -- [1,2] -- -- >>> drop 0 [1,2] -- [1,2] ---- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. drop :: Int -> [a] -> [a] -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
-- >>> splitAt 6 "Hello World!" -- ("Hello ","World!") -- -- >>> splitAt 3 [1,2,3,4,5] -- ([1,2,3],[4,5]) -- -- >>> splitAt 1 [1,2,3] -- ([1],[2,3]) -- -- >>> splitAt 3 [1,2,3] -- ([1,2,3],[]) -- -- >>> splitAt 4 [1,2,3] -- ([1,2,3],[]) -- -- >>> splitAt 0 [1,2,3] -- ([],[1,2,3]) -- -- >>> splitAt (-1) [1,2,3] -- ([],[1,2,3]) ---- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) -- | takeWhile, applied to a predicate p and a list -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p. -- --
-- >>> takeWhile (< 3) [1,2,3,4,1,2,3,4] -- [1,2] -- -- >>> takeWhile (< 9) [1,2,3] -- [1,2,3] -- -- >>> takeWhile (< 0) [1,2,3] -- [] --takeWhile :: (a -> Bool) -> [a] -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. -- --
-- >>> dropWhile (< 3) [1,2,3,4,5,1,2,3] -- [3,4,5,1,2,3] -- -- >>> dropWhile (< 9) [1,2,3] -- [] -- -- >>> dropWhile (< 0) [1,2,3] -- [1,2,3] --dropWhile :: (a -> Bool) -> [a] -> [a] -- | The dropWhileEnd function drops the largest suffix of a list in -- which the given predicate holds for all elements. For example: -- --
-- >>> dropWhileEnd isSpace "foo\n" -- "foo" ---- --
-- >>> dropWhileEnd isSpace "foo bar" -- "foo bar" ---- --
-- dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined --dropWhileEnd :: (a -> Bool) -> [a] -> [a] -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is longest prefix (possibly empty) -- of xs of elements that satisfy p and second element -- is the remainder of the list: -- --
-- >>> span (< 3) [1,2,3,4,1,2,3,4] -- ([1,2],[3,4,1,2,3,4]) -- -- >>> span (< 9) [1,2,3] -- ([1,2,3],[]) -- -- >>> span (< 0) [1,2,3] -- ([],[1,2,3]) ---- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | break, applied to a predicate p and a list -- xs, returns a tuple where first element is longest prefix -- (possibly empty) of xs of elements that do not satisfy -- p and second element is the remainder of the list: -- --
-- >>> break (> 3) [1,2,3,4,1,2,3,4] -- ([1,2,3],[4,1,2,3,4]) -- -- >>> break (< 9) [1,2,3] -- ([],[1,2,3]) -- -- >>> break (> 9) [1,2,3] -- ([1,2,3],[]) ---- -- break p is equivalent to span (not . -- p). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | <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. -- --
-- >>> stripPrefix "foo" "foobar" -- Just "bar" ---- --
-- >>> stripPrefix "foo" "foo" -- Just "" ---- --
-- >>> stripPrefix "foo" "barfoo" -- Nothing ---- --
-- >>> stripPrefix "foo" "barfoobaz" -- Nothing --stripPrefix :: Eq a => [a] -> [a] -> Maybe [a] -- | The group function takes a list and returns a list of lists -- such that the concatenation of the result is equal to the argument. -- Moreover, each sublist in the result contains only equal elements. For -- example, -- --
-- >>> group "Mississippi" -- ["M","i","ss","i","ss","i","pp","i"] ---- -- It is a special case of groupBy, which allows the programmer to -- supply their own equality test. group :: Eq a => [a] -> [[a]] -- | The inits function returns all initial segments of the -- argument, shortest first. For example, -- --
-- >>> inits "abc" -- ["","a","ab","abc"] ---- -- Note that inits has the following strictness property: -- inits (xs ++ _|_) = inits xs ++ _|_ -- -- In particular, inits _|_ = [] : _|_ inits :: [a] -> [[a]] -- | <math>. The tails function returns all final segments of -- the argument, longest first. For example, -- --
-- >>> tails "abc" -- ["abc","bc","c",""] ---- -- Note that tails has the following strictness property: -- tails _|_ = _|_ : _|_ tails :: [a] -> [[a]] -- | <math>. The isPrefixOf function takes two lists and -- returns True iff the first list is a prefix of the second. -- --
-- >>> "Hello" `isPrefixOf` "Hello World!" -- True ---- --
-- >>> "Hello" `isPrefixOf` "Wello Horld!" -- False --isPrefixOf :: Eq a => [a] -> [a] -> Bool -- | The isSuffixOf function takes two lists and returns True -- iff the first list is a suffix of the second. The second list must be -- finite. -- --
-- >>> "ld!" `isSuffixOf` "Hello World!" -- True ---- --
-- >>> "World" `isSuffixOf` "Hello World!" -- False --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. -- --
-- >>> isInfixOf "Haskell" "I really like Haskell." -- True ---- --
-- >>> isInfixOf "Ial" "I really like Haskell." -- False --isInfixOf :: Eq a => [a] -> [a] -> Bool -- | elem is the list membership predicate, usually written in infix -- form, e.g., x `elem` xs. For the result to be False, -- the list must be finite; True, however, results from an element -- equal to x found at a finite index of a finite or infinite -- list. -- --
-- >>> 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. -- --
-- >>> 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` -- | <math>. lookup key assocs looks up a key in an -- association list. -- --
-- >>> 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 list and returns the -- first element in the list matching the predicate, or Nothing if -- there is no such element. -- --
-- >>> find (> 4) [1..] -- Just 5 ---- --
-- >>> find (< 0) [1..10] -- Nothing --find :: (a -> Bool) -> [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] ---- --
-- >>> filter odd [1, 2, 3] -- [1,3] --filter :: (a -> Bool) -> [a] -> [a] -- | The partition function takes a predicate a list and returns the -- pair of lists of elements which do and do not satisfy the predicate, -- respectively; i.e., -- --
-- partition p xs == (filter p xs, filter (not . p) xs) ---- --
-- >>> partition (`elem` "aeiou") "Hello World!" -- ("eoo","Hll Wrld!") --partition :: (a -> Bool) -> [a] -> ([a], [a]) -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. -- --
-- >>> ['a', '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 --(!!) :: [a] -> Int -> a infixl 9 !! -- | The elemIndex function returns the index of the first element -- in the given list which is equal (by ==) to the query element, -- or Nothing if there is no such element. -- --
-- >>> elemIndex 4 [0..] -- Just 4 --elemIndex :: Eq a => a -> [a] -> Maybe Int -- | The elemIndices function extends elemIndex, by returning -- the indices of all elements equal to the query element, in ascending -- order. -- --
-- >>> elemIndices 'o' "Hello World" -- [4,7] --elemIndices :: Eq a => a -> [a] -> [Int] -- | The findIndex function takes a predicate and a list and returns -- the index of the first element in the list satisfying the predicate, -- or Nothing if there is no such element. -- --
-- >>> findIndex isSpace "Hello World!" -- Just 5 --findIndex :: (a -> Bool) -> [a] -> Maybe Int -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. -- --
-- >>> findIndices (`elem` "aeiou") "Hello World!" -- [1,4,7] --findIndices :: (a -> Bool) -> [a] -> [Int] -- | <math>. zip takes two lists and returns a list of -- corresponding pairs. -- --
-- >>> zip [1, 2] ['a', 'b'] -- [(1, 'a'), (2, 'b')] ---- -- 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 is right-lazy: -- --
-- >>> zip [] _|_ -- [] -- -- >>> zip _|_ [] -- _|_ ---- -- zip is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. 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..] ---- -- For example, zipWith (+) is applied to two lists to -- produce the list of corresponding sums: -- --
-- >>> zipWith (+) [1, 2, 3] [4, 5, 6] -- [5,7,9] ---- -- zipWith is right-lazy: -- --
-- >>> zipWith f [] _|_ -- [] ---- -- zipWith is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | The zipWith3 function takes a function which combines three -- elements, as well as three lists and returns a list of 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..] --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. -- --
-- >>> 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, analogous to unzip. -- --
-- >>> 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]) -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
-- >>> lines "" -- [] ---- --
-- >>> lines "\n" -- [""] ---- --
-- >>> lines "one" -- ["one"] ---- --
-- >>> lines "one\n" -- ["one"] ---- --
-- >>> lines "one\n\n" -- ["one",""] ---- --
-- >>> lines "one\ntwo" -- ["one","two"] ---- --
-- >>> lines "one\ntwo\n" -- ["one","two"] ---- -- Thus lines s contains at least as many elements as -- newlines in s. lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space. -- --
-- >>> words "Lorem ipsum\ndolor" -- ["Lorem","ipsum","dolor"] --words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. -- --
-- >>> unlines ["Hello", "World", "!"] -- "Hello\nWorld\n!\n" --unlines :: [String] -> String -- | unwords is an inverse operation to words. It joins words -- with separating spaces. -- --
-- >>> unwords ["Lorem", "ipsum", "dolor"] -- "Lorem ipsum dolor" --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. -- --
-- >>> nub [1,2,3,4,3,2,1,2,4,3,5] -- [1,2,3,4,5] --nub :: Eq a => [a] -> [a] -- | <math>. delete x removes the first occurrence of -- x from its list argument. For example, -- --
-- >>> delete 'a' "banana" -- "bnana" ---- -- It is a special case of deleteBy, which allows the programmer -- to supply their own equality test. delete :: Eq a => a -> [a] -> [a] -- | The \\ function is list difference (non-associative). In the -- result of xs \\ ys, the first occurrence of -- each element of ys in turn (if any) has been removed from -- xs. Thus -- --
-- (xs ++ ys) \\ xs == ys. ---- --
-- >>> "Hello World!" \\ "ell W" -- "Hoorld!" ---- -- It is a special case of deleteFirstsBy, which allows the -- programmer to supply their own equality test. (\\) :: Eq a => [a] -> [a] -> [a] infix 5 \\ -- | The union function returns the list union of the two lists. For -- example, -- --
-- >>> "dog" `union` "cow" -- "dogcw" ---- -- Duplicates, and elements of the first list, are removed from the the -- second list, but if the first list contains duplicates, so will the -- result. It is a special case of unionBy, which allows the -- programmer to supply their own equality test. union :: Eq a => [a] -> [a] -> [a] -- | The intersect function takes the list intersection of two -- lists. For example, -- --
-- >>> [1,2,3,4] `intersect` [2,4,6,8] -- [2,4] ---- -- If the first list contains duplicates, so will the result. -- --
-- >>> [1,2,2,3,4] `intersect` [6,4,4,2] -- [2,2,4] ---- -- It is a special case of intersectBy, which allows the -- programmer to supply their own equality test. If the element is found -- in both the first and the second list, the element from the first list -- will be used. intersect :: Eq a => [a] -> [a] -> [a] -- | The sort function implements a stable sorting algorithm. It is -- a special case of sortBy, which allows the programmer to supply -- their own comparison function. -- -- Elements are arranged from lowest to highest, keeping duplicates in -- the order they appeared in the input. -- --
-- >>> sort [1,6,4,3,2,5] -- [1,2,3,4,5,6] --sort :: Ord a => [a] -> [a] -- | Sort a list by comparing the results of a key function applied to each -- element. sortOn f is equivalent to sortBy (comparing -- f), but has the performance advantage of only evaluating -- f once for each element in the input list. This is called the -- decorate-sort-undecorate paradigm, or Schwartzian transform. -- -- Elements are arranged from from lowest to highest, keeping duplicates -- in the order they appeared in the input. -- --
-- >>> sortOn fst [(2, "world"), (4, "!"), (1, "Hello")] -- [(1,"Hello"),(2,"world"),(4,"!")] --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. -- --
-- >>> 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. -- --
-- >>> nubBy (\x y -> mod x 3 == mod y 3) [1,2,4,5,6] -- [1,2,6] --nubBy :: (a -> a -> Bool) -> [a] -> [a] -- | <math>. The deleteBy function behaves like delete, -- but takes a user-supplied equality predicate. -- --
-- >>> deleteBy (<=) 4 [1..10] -- [1,2,3,5,6,7,8,9,10] --deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a] -- | The deleteFirstsBy function takes a predicate and two lists and -- returns the first list with the first occurrence of each element of -- the second list removed. deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The unionBy function is the non-overloaded version of -- union. unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The intersectBy function is the non-overloaded version of -- intersect. intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (a -> a -> Bool) -> [a] -> [[a]] -- | The sortBy function is the non-overloaded version of -- sort. -- --
-- >>> sortBy (\(a,_) (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. insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] -- | The maximumBy function takes a comparison function and a list -- and returns the greatest element of the list by the comparison -- function. The list must be finite and non-empty. -- -- 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" --maximumBy :: (a -> a -> Ordering) -> [a] -> a -- | The minimumBy function takes a comparison function and a list -- and returns the least element of the list by the comparison function. -- The list must be finite and non-empty. -- -- 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 -> a -> Ordering) -> [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. -- --
-- >>> genericLength [1, 2, 3] :: Int -- 3 -- -- >>> genericLength [1, 2, 3] :: Float -- 3.0 --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 -- | Data structures that can be folded. -- -- For example, given a data type -- --
-- data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) ---- -- a suitable instance would be -- --
-- instance Foldable Tree where -- foldMap f Empty = mempty -- foldMap f (Leaf x) = f x -- foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r ---- -- This is suitable even for abstract types, as the monoid is assumed to -- satisfy the monoid laws. Alternatively, one could define -- foldr: -- --
-- instance Foldable Tree where -- foldr f z Empty = z -- foldr f z (Leaf x) = f x z -- foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l ---- -- Foldable instances are expected to satisfy the following -- laws: -- --
-- foldr f z t = appEndo (foldMap (Endo . f) t ) z ---- --
-- foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z ---- --
-- fold = foldMap id ---- --
-- length = getSum . foldMap (Sum . const 1) ---- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
-- sum = getSum . foldMap Sum ---- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
-- foldMap f = fold . fmap f ---- -- which implies that -- --
-- foldMap f . fmap g = foldMap (f . g) --class Foldable t -- | Combine the elements of a structure using a monoid. -- --
-- >>> fold [[1, 2, 3], [4, 5], [6], []] -- [1,2,3,4,5,6] ---- --
-- >>> fold [Sum 1, Sum 3, Sum 5] -- Sum {getSum = 9} ---- -- Infinite structures never terminate: -- --
-- >>> fold (repeat Nothing) -- * Hangs forever * --fold :: (Foldable t, Monoid m) => t m -> m -- | Map each element of the structure to a monoid, and combine the -- results. -- --
-- >>> 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] ---- -- Infinite structures never terminate: -- --
-- >>> foldMap Sum [1..] -- * Hangs forever * --foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | A variant of foldMap that is strict in the accumulator. foldMap' :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | Right-associative fold of a structure. -- -- In the case of lists, foldr, when applied to a binary operator, -- a starting value (typically the right-identity of the operator), and a -- list, reduces the list using the binary operator, from right to left: -- --
-- foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) ---- -- Note that, since the head of the resulting expression is produced by -- an application of the operator to the first element of the list, -- foldr can produce a terminating expression from an infinite -- list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldr f z = foldr f z . toList ---- --
-- >>> foldr (||) False [False, True, False] -- True ---- --
-- >>> foldr (||) False [] -- False ---- --
-- >>> foldr (\nextChar reversedString -> reversedString ++ [nextChar]) "foo" ['a', 'b', 'c', 'd'] -- "foodcba" ---- --
-- >>> foldr (||) False (True : repeat False) -- True ---- -- But the following doesn't terminate: -- --
-- >>> foldr (||) False (repeat False ++ [True]) -- * Hangs forever * ---- --
-- >>> foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (repeat 1) -- [1,4,7,10,13,16,19,22,25,28,31,34,37,40,43... ---- --
-- >>> take 5 $ foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (repeat 1) -- [1,4,7,10,13] --foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Right-associative fold of a structure, but with strict application of -- the operator. foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Left-associative fold of a structure. -- -- In the case of lists, foldl, when applied to a binary operator, -- a starting value (typically the left-identity of the operator), and a -- list, reduces the list using the binary operator, from left to right: -- --
-- foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn ---- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldl' -- will diverge if given an infinite list. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is -- that latter does not force the "inner" results (e.g. z `f` x1 -- in the above example) before applying them to the operator (e.g. to -- (`f` x2)). This results in a thunk chain <math> -- elements long, which then must be evaluated from the outside-in. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldl f z = foldl f z . toList ---- --
-- >>> foldl (+) 42 (Node (Leaf 1) 3 (Node Empty 4 (Leaf 2))) -- 52 ---- --
-- >>> foldl (+) 42 Empty -- 42 ---- --
-- >>> foldl (\string nextElement -> nextElement : string) "abcd" (Node (Leaf 'd') 'e' (Node Empty 'f' (Leaf 'g'))) -- "gfedabcd" ---- -- Left-folding infinite structures never terminates: -- --
-- >>> let infiniteNode = Node Empty 1 infiniteNode in foldl (+) 42 infiniteNode -- * Hangs forever * ---- -- Evaluating the head of the result (when applicable) does not -- terminate, unlike foldr: -- --
-- >>> let infiniteNode = Node Empty 'd' infiniteNode in take 5 (foldl (\string nextElement -> nextElement : string) "abc" infiniteNode) -- * Hangs forever * --foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | Left-associative fold of a structure but with strict application of -- the operator. -- -- This ensures that each step of the fold is forced to weak head normal -- form before being applied, avoiding the collection of thunks that -- would otherwise occur. This is often what you want to strictly reduce -- a finite list to a single, monolithic result (e.g. length). -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldl' f z = foldl' f z . toList --foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | A variant of foldr that has no base case, and thus may only be -- applied to non-empty structures. -- -- ⚠️ This function is non-total and will raise a runtime exception if -- the structure happens to be empty. -- --
-- >>> 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 ---- --
-- >>> 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. -- --
-- >>> 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 -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. -- --
-- >>> null [] -- True ---- --
-- >>> null [1] -- False ---- -- null terminates even for infinite structures: -- --
-- >>> null [1..] -- False --null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. -- --
-- >>> length [] -- 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. -- --
-- >>> 3 `elem` [] -- False ---- --
-- >>> 3 `elem` [1,2] -- False ---- --
-- >>> 3 `elem` [1,2,3,4,5] -- True ---- -- For infinite structures, elem terminates if the 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. -- --
-- >>> maximum [1..10] -- 10 ---- --
-- >>> maximum [] -- *** Exception: Prelude.maximum: empty list ---- --
-- >>> maximum Nothing -- *** Exception: maximum: empty structure --maximum :: forall a. (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 -- --
-- >>> minimum [1..10] -- 1 ---- --
-- >>> minimum [] -- *** Exception: Prelude.minimum: empty list ---- --
-- >>> minimum Nothing -- *** Exception: minimum: empty structure --minimum :: forall a. (Foldable t, Ord a) => t a -> a -- | The sum function computes the sum of the numbers of a -- structure. -- --
-- >>> sum [] -- 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. -- --
-- >>> 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` -- | Monadic fold over the elements of a structure, associating to the -- right, i.e. from right to left. -- --
-- >>> foldrM (\string acc -> print string >> pure (acc + length string)) 42 ["Hello", "world", "!"] -- "!" -- "world" -- "Hello" -- 53 --foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b -- | Monadic fold over the elements of a structure, associating to the -- left, i.e. from left to right. -- --
-- >>> foldlM (\acc string -> print string >> pure (acc + length string)) 42 ["Hello", "world", "!"] -- "Hello" -- "world" -- "!" -- 53 --foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and ignore the results. For a version that doesn't -- ignore the results see traverse. -- --
-- >>> traverse_ 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. -- --
-- >>> 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_ [print "Hello", print "world", print "!"] -- "Hello" -- "world" -- "!" --sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () -- | The sum of a collection of actions, generalizing concat. -- --
-- >>> 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. -- -- As of base 4.8.0.0, mapM_ is just traverse_, specialized -- to Monad. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () -- | forM_ is mapM_ with its arguments flipped. For a version -- that doesn't ignore the results see forM. -- -- As of base 4.8.0.0, forM_ is just for_, specialized to -- Monad. forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m () -- | Evaluate each monadic action in the structure from left to right, and -- ignore the results. For a version that doesn't ignore the results see -- sequence. -- -- As of base 4.8.0.0, sequence_ is just sequenceA_, -- specialized to Monad. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | The sum of a collection of actions, generalizing concat. As of -- base 4.8.0.0, msum is just asum, specialized to -- MonadPlus. msum :: (Foldable t, MonadPlus m) => t (m a) -> m a -- | The concatenation of all the elements of a container of lists. -- --
-- >>> concat (Just [1, 2, 3]) -- [1,2,3] ---- --
-- >>> concat (Node (Leaf [1, 2, 3]) [4, 5] (Node Empty [6] (Leaf []))) -- [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. -- --
-- >>> concatMap (take 3) [[1..], [10..], [100..], [1000..]] -- [1,2,3,10,11,12,100,101,102,1000,1001,1002] ---- --
-- >>> concatMap (take 3) (Node (Leaf [1..]) [10..] Empty) -- [1,2,3,10,11,12] --concatMap :: Foldable t => (a -> [b]) -> t a -> [b] -- | and returns the conjunction of a container of Bools. For the -- result to be True, the container must be finite; False, -- however, results from a False value finitely far from the left -- end. -- --
-- >>> and [] -- 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 :: Foldable t => t Bool -> Bool -- | or returns the disjunction of a container of Bools. For the -- result to be False, the container must be finite; True, -- however, results from a True value finitely far from the left -- end. -- --
-- >>> or [] -- 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 :: Foldable t => t Bool -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"] -- "Longest" --maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | The least element of a non-empty structure with respect to the given -- comparison function. -- --
-- >>> minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"] -- "!" --minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | notElem is the negation of elem. -- --
-- >>> 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. -- --
-- >>> find (> 42) [0, 5..] -- Just 45 ---- --
-- >>> find (> 4) (Node (Leaf 3) 17 (Node Empty 12 (Leaf 8))) -- Just 17 ---- --
-- >>> find (> 12) [1..7] -- Nothing --find :: Foldable t => (a -> Bool) -> t a -> Maybe a instance Data.Foldable.Foldable GHC.Generics.V1 instance Data.Foldable.Foldable GHC.Generics.Par1 instance Data.Foldable.Foldable f => Data.Foldable.Foldable (GHC.Generics.Rec1 f) instance Data.Foldable.Foldable (GHC.Generics.K1 i c) instance Data.Foldable.Foldable f => Data.Foldable.Foldable (GHC.Generics.M1 i c f) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (f GHC.Generics.:+: g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (f GHC.Generics.:*: g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (f GHC.Generics.:.: g) instance Data.Foldable.Foldable GHC.Generics.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 Data.Ord.Down instance Data.Foldable.Foldable GHC.Maybe.Maybe instance Data.Foldable.Foldable [] instance Data.Foldable.Foldable GHC.Base.NonEmpty instance Data.Foldable.Foldable (Data.Either.Either a) instance Data.Foldable.Foldable ((,) a) instance Data.Foldable.Foldable (GHC.Arr.Array i) instance Data.Foldable.Foldable Data.Proxy.Proxy instance Data.Foldable.Foldable Data.Semigroup.Internal.Dual instance Data.Foldable.Foldable Data.Semigroup.Internal.Sum instance Data.Foldable.Foldable Data.Semigroup.Internal.Product instance Data.Foldable.Foldable Data.Monoid.First instance Data.Foldable.Foldable Data.Monoid.Last 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.Generics.U1 module Data.Functor.Const -- | The Const functor. newtype Const a b Const :: a -> Const a b [getConst] :: Const a b -> a instance forall a k (b :: k). Foreign.Storable.Storable a => Foreign.Storable.Storable (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Float.RealFloat a => GHC.Float.RealFloat (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Real.RealFrac a => GHC.Real.RealFrac (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Real.Real a => GHC.Real.Real (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Classes.Ord a => GHC.Classes.Ord (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Num.Num a => GHC.Num.Num (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Base.Monoid a => GHC.Base.Monoid (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Base.Semigroup a => GHC.Base.Semigroup (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.Real.Integral a => GHC.Real.Integral (Data.Functor.Const.Const a b) instance GHC.Generics.Generic1 (Data.Functor.Const.Const a) instance forall a k (b :: k). GHC.Generics.Generic (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Real.Fractional a => GHC.Real.Fractional (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Float.Floating a => GHC.Float.Floating (Data.Functor.Const.Const a b) instance forall a k (b :: k). Data.Bits.FiniteBits a => Data.Bits.FiniteBits (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Classes.Eq a => GHC.Classes.Eq (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Enum.Enum a => GHC.Enum.Enum (Data.Functor.Const.Const a b) instance forall a k (b :: k). GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Functor.Const.Const a b) instance forall a k (b :: k). Data.Bits.Bits a => Data.Bits.Bits (Data.Functor.Const.Const a b) instance forall k a (b :: k). GHC.Read.Read a => GHC.Read.Read (Data.Functor.Const.Const a b) instance forall k a (b :: k). GHC.Show.Show a => GHC.Show.Show (Data.Functor.Const.Const a b) instance Data.Foldable.Foldable (Data.Functor.Const.Const m) instance GHC.Base.Functor (Data.Functor.Const.Const m) instance GHC.Base.Monoid m => GHC.Base.Applicative (Data.Functor.Const.Const m) -- | This module is part of the Foreign Function Interface (FFI) and will -- usually be imported via the module Foreign. module Foreign.StablePtr -- | A stable pointer is a reference to a Haskell expression that is -- guaranteed not to be affected by garbage collection, i.e., it will -- neither be deallocated nor will the value of the stable pointer itself -- change during garbage collection (ordinary references may be relocated -- during garbage collection). Consequently, stable pointers can be -- passed to foreign code, which can treat it as an opaque reference to a -- Haskell value. -- -- A value of type StablePtr a is a stable pointer to a Haskell -- expression of type a. data {-# CTYPE "HsStablePtr" #-} StablePtr a -- | Create a stable pointer referring to the given Haskell value. newStablePtr :: a -> IO (StablePtr a) -- | Obtain the Haskell value referenced by a stable pointer, i.e., the -- same value that was passed to the corresponding call to -- 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 may -- not refer to an accessible memory location and any attempt to pass it -- to the member functions of the class Storable leads to -- undefined behaviour. castStablePtrToPtr :: StablePtr a -> Ptr () -- | The inverse of castStablePtrToPtr, i.e., we have the identity -- --
-- sp == castPtrToStablePtr (castStablePtrToPtr sp) ---- -- for any stable pointer sp on which freeStablePtr has -- not been executed yet. Moreover, castPtrToStablePtr may only be -- applied to pointers that have been produced by -- castStablePtrToPtr. castPtrToStablePtr :: Ptr () -> StablePtr a -- | This provides a type-indexed type representation mechanism, similar to -- that described by, -- --
-- 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 :: k2). () => forall k1 (a :: k1 -> k2) (b :: k1). t ~ a b => TypeRep a -> TypeRep b -> TypeRep t -- | Pattern match on a type constructor pattern Con :: forall k (a :: k). () => IsApplication 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' :: forall k (a :: k). () => IsApplication a ~ "" => TyCon -> [SomeTypeRep] -> TypeRep a -- | The function type constructor. -- -- For instance, -- --
-- typeRep @(Int -> Char) === Fun (typeRep @Int) (typeRep @Char) --pattern Fun :: forall k (fun :: k). () => forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (arg :: TYPE r1) (res :: TYPE r2). (k ~ Type, fun ~~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun -- | Observe the type constructor of a type representation typeRepTyCon :: TypeRep a -> TyCon -- | Helper to fully evaluate TypeRep for use as -- NFData(rnf) implementation rnfTypeRep :: TypeRep a -> () -- | Type equality eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Maybe (a :~~: b) -- | Observe the kind of a type. typeRepKind :: TypeRep a :: k -> TypeRep k splitApps :: TypeRep a -> (TyCon, [SomeTypeRep]) -- | A non-indexed type representation. data SomeTypeRep [SomeTypeRep] :: forall k (a :: k). !TypeRep a -> SomeTypeRep -- | Takes a value of type a and returns a concrete representation -- of that type. someTypeRep :: forall proxy a. Typeable a => proxy a -> SomeTypeRep -- | Observe the type constructor of a quantified type representation. someTypeRepTyCon :: SomeTypeRep -> TyCon -- | Helper to fully evaluate SomeTypeRep for use as -- NFData(rnf) implementation rnfSomeTypeRep :: SomeTypeRep -> () data TyCon tyConPackage :: TyCon -> String tyConModule :: TyCon -> String tyConName :: TyCon -> String rnfTyCon :: TyCon -> () data Module moduleName :: Module -> String modulePackage :: Module -> String -- | Helper to fully evaluate TyCon for use as NFData(rnf) -- implementation rnfModule :: Module -> () -- | The Typeable class reifies types to some extent by associating -- type representations to types. These type representations can be -- compared, and one can in turn define a type-safe cast operation. To -- this end, an unsafe cast is guarded by a test for type -- (representation) equivalence. The module Data.Dynamic uses -- Typeable for an implementation of dynamics. The module -- Data.Data uses Typeable and type-safe cast (but not dynamics) -- to support the "Scrap your boilerplate" style of generic programming. -- --
-- >>> 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 Proxy :: Proxy t -- | A quantified type representation. type TypeRep = SomeTypeRep -- | Force a TypeRep to normal form. rnfTypeRep :: TypeRep -> () -- | Show a type representation showsTypeRep :: TypeRep -> ShowS -- | Build a function type. mkFunTy :: TypeRep -> TypeRep -> TypeRep -- | Applies a type to a function type. Returns: Just u if the -- first argument represents a function of type t -> u and -- the second argument represents a function of type t. -- Otherwise, returns Nothing. funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep -- | Splits a type constructor application. Note that if the type -- constructor is polymorphic, this will not return the kinds that were -- used. splitTyConApp :: TypeRep -> (TyCon, [TypeRep]) -- | Observe the argument types of a type representation typeRepArgs :: TypeRep -> [TypeRep] -- | Observe the type constructor of a quantified type representation. typeRepTyCon :: TypeRep -> TyCon -- | Takes a value of type a and returns a concrete representation -- of that type. typeRepFingerprint :: TypeRep -> Fingerprint data TyCon tyConPackage :: TyCon -> String tyConModule :: TyCon -> String tyConName :: TyCon -> String rnfTyCon :: TyCon -> () tyConFingerprint :: TyCon -> Fingerprint typeOf1 :: forall t (a :: Type). Typeable t => t a -> TypeRep typeOf2 :: forall t (a :: Type) (b :: Type). Typeable t => t a b -> TypeRep typeOf3 :: forall t (a :: Type) (b :: Type) (c :: Type). Typeable t => t a b c -> TypeRep typeOf4 :: forall t (a :: Type) (b :: Type) (c :: Type) (d :: Type). Typeable t => t a b c d -> TypeRep typeOf5 :: forall t (a :: Type) (b :: Type) (c :: Type) (d :: Type) (e :: Type). Typeable t => t a b c d e -> TypeRep typeOf6 :: forall t (a :: Type) (b :: Type) (c :: Type) (d :: Type) (e :: Type) (f :: Type). Typeable t => t a b c d e f -> TypeRep typeOf7 :: forall t (a :: Type) (b :: Type) (c :: Type) (d :: Type) (e :: Type) (f :: Type) (g :: Type). Typeable t => t a b c d e f g -> TypeRep -- | 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.Ord GHC.Exception.Type.ArithException instance GHC.Classes.Eq GHC.Exception.Type.ArithException instance GHC.Exception.Type.Exception GHC.Exception.Type.ArithException instance GHC.Show.Show GHC.Exception.Type.ArithException instance GHC.Show.Show GHC.Exception.Type.SomeException instance GHC.Exception.Type.Exception 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. throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall 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>:2:1 in interactive:Ghci1 ---- -- GHC solves HasCallStack constraints in three steps: -- --
-- test :: IORef [a] -- test = unsafePerformIO $ newIORef [] -- -- main = do -- writeIORef test [42] -- bang <- readIORef test -- print (bang :: [Char]) ---- -- This program will core dump. This problem with polymorphic references -- is well known in the ML community, and does not arise with normal -- monadic use of references. There is no easy way to make it impossible -- once you use unsafePerformIO. Indeed, it is possible to write -- coerce :: a -> b with the help of unsafePerformIO. -- So be careful! unsafePerformIO :: IO a -> a -- | 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 a 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` x ===> throw e -- throwIO e `seq` x ===> x ---- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwIO will only cause -- an exception to be raised when it is used within the IO monad. -- The throwIO variant should be used in preference to -- throw to raise an exception within the IO monad because -- it guarantees ordering with respect to other IO operations, -- whereas throw does not. throwIO :: Exception e => e -> IO a -- | 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.Show.Show GHC.IO.MaskingState instance GHC.Classes.Eq GHC.IO.MaskingState -- | The IORef type module GHC.IORef -- | A mutable variable in the IO monad newtype IORef a IORef :: STRef RealWorld a -> IORef a -- | Build a new IORef newIORef :: a -> IO (IORef a) -- | Read the value of an IORef readIORef :: IORef a -> IO a -- | Write a new value into an IORef writeIORef :: IORef a -> a -> IO () atomicModifyIORef2Lazy :: IORef a -> (a -> (a, b)) -> IO (a, (a, b)) 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 -- | Strict version of atomicModifyIORef. This forces both the value -- stored in the IORef and the value returned. The new value is -- installed in the IORef before the returned value is forced. So -- --
-- atomicModifyIORef' ref (x -> (x+1, undefined)) ---- -- will increment the IORef and then throw an exception in the -- calling thread. 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 ancilliary *unmanaged* memory pointed to by the -- MutableByteArray#. See the zlib library for an example -- of this use. -- --
-- 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. The -- storage manager will start the finalizer, in a separate thread, some -- time after the last reference to the ForeignPtr is dropped. -- There is no guarantee of promptness, and in fact there is no guarantee -- that the finalizer will eventually run at all. -- -- Note that references from a finalizer do not necessarily prevent -- another object from being finalized. If A's finalizer refers to B -- (perhaps using touchForeignPtr, then the only guarantee is that -- B's finalizer will never be started before A's. If both A and B are -- unreachable, then both finalizers will start together. See -- touchForeignPtr for more on finalizer ordering. 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 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). 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 function ensures that the foreign object in question is alive at -- the given place in the sequence of IO actions. In particular -- withForeignPtr does a touchForeignPtr after it executes -- the user action. -- -- Note that this function should not be used to express dependencies -- between finalizers on ForeignPtrs. For example, if the -- finalizer for a ForeignPtr F1 calls -- touchForeignPtr on a second ForeignPtr F2, then -- the only guarantee is that the finalizer for F2 is never -- started before the finalizer for F1. They might be started -- together if for example both F1 and F2 are otherwise -- unreachable, and in that case the scheduler might end up running the -- finalizer for F2 first. -- -- In general, it is not recommended to use finalizers on separate -- objects with ordering constraints between them. To express the -- ordering robustly requires explicit synchronisation using -- MVars between the finalizers, but even then the runtime -- sometimes runs multiple finalizers sequentially in a single thread -- (for performance reasons), so synchronisation between finalizers could -- result in artificial deadlock. Another alternative is to use explicit -- reference counting. touchForeignPtr :: ForeignPtr a -> IO () -- | 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. 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. finalizeForeignPtr :: ForeignPtr a -> IO () -- | This function ensures that the foreign object in question is alive at -- the given place in the sequence of IO actions. In particular -- withForeignPtr does a touchForeignPtr after it executes -- the user action. -- -- Note that this function should not be used to express dependencies -- between finalizers on ForeignPtrs. For example, if the -- finalizer for a ForeignPtr F1 calls -- touchForeignPtr on a second ForeignPtr F2, then -- the only guarantee is that the finalizer for F2 is never -- started before the finalizer for F1. They might be started -- together if for example both F1 and F2 are otherwise -- unreachable, and in that case the scheduler might end up running the -- finalizer for F2 first. -- -- In general, it is not recommended to use finalizers on separate -- objects with ordering constraints between them. To express the -- ordering robustly requires explicit synchronisation using -- MVars between the finalizers, but even then the runtime -- sometimes runs multiple finalizers sequentially in a single thread -- (for performance reasons), so synchronisation between finalizers could -- result in artificial deadlock. Another alternative is to use explicit -- reference counting. touchForeignPtr :: ForeignPtr a -> IO () -- | This function casts a ForeignPtr parameterised by one type into -- another type. castForeignPtr :: ForeignPtr a -> ForeignPtr b -- | Allocate some memory and return a ForeignPtr to it. The memory -- will be released automatically when the ForeignPtr is -- discarded. -- -- mallocForeignPtr is equivalent to -- --
-- do { p <- malloc; newForeignPtr finalizerFree p } ---- -- although it may be implemented differently internally: you may not -- assume that the memory returned by mallocForeignPtr has been -- allocated with malloc. -- -- GHC notes: mallocForeignPtr has a heavily optimised -- implementation in GHC. It uses pinned memory in the garbage collected -- heap, so the ForeignPtr does not require a finalizer to free -- the memory. Use of mallocForeignPtr and associated functions is -- strongly recommended in preference to newForeignPtr with a -- finalizer. mallocForeignPtr :: Storable a => IO (ForeignPtr a) -- | This function is similar to mallocForeignPtr, except that the -- size of the memory required is given explicitly as a number of bytes. mallocForeignPtrBytes :: Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray0, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray0 :: Storable a => Int -> IO (ForeignPtr a) -- | The ForeignPtr type and operations. This module is part of the -- Foreign Function Interface (FFI) and will usually be imported via the -- Foreign module. -- -- 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. finalizeForeignPtr :: ForeignPtr a -> IO () -- | This function ensures that the foreign object in question is alive at -- the given place in the sequence of IO actions. In particular -- withForeignPtr does a touchForeignPtr after it executes -- the user action. -- -- Note that this function should not be used to express dependencies -- between finalizers on ForeignPtrs. For example, if the -- finalizer for a ForeignPtr F1 calls -- touchForeignPtr on a second ForeignPtr F2, then -- the only guarantee is that the finalizer for F2 is never -- started before the finalizer for F1. They might be started -- together if for example both F1 and F2 are otherwise -- unreachable, and in that case the scheduler might end up running the -- finalizer for F2 first. -- -- In general, it is not recommended to use finalizers on separate -- objects with ordering constraints between them. To express the -- ordering robustly requires explicit synchronisation using -- MVars between the finalizers, but even then the runtime -- sometimes runs multiple finalizers sequentially in a single thread -- (for performance reasons), so synchronisation between finalizers could -- result in artificial deadlock. Another alternative is to use explicit -- reference counting. touchForeignPtr :: ForeignPtr a -> IO () -- | This function casts a ForeignPtr parameterised by one type into -- another type. castForeignPtr :: ForeignPtr a -> ForeignPtr b -- | Advances the given address by the given offset in bytes. -- -- The new ForeignPtr shares the finalizer of the original, -- equivalent from a finalization standpoint to just creating another -- reference to the original. That is, the finalizer will not be called -- before the new ForeignPtr is unreachable, nor will it be called -- an additional time due to this call, and the finalizer will be called -- with the same address that it would have had this call not happened, -- *not* the new address. plusForeignPtr :: ForeignPtr a -> Int -> ForeignPtr b -- | Allocate some memory and return a ForeignPtr to it. The memory -- will be released automatically when the ForeignPtr is -- discarded. -- -- mallocForeignPtr is equivalent to -- --
-- do { p <- malloc; newForeignPtr finalizerFree p } ---- -- although it may be implemented differently internally: you may not -- assume that the memory returned by mallocForeignPtr has been -- allocated with malloc. -- -- GHC notes: mallocForeignPtr has a heavily optimised -- implementation in GHC. It uses pinned memory in the garbage collected -- heap, so the ForeignPtr does not require a finalizer to free -- the memory. Use of mallocForeignPtr and associated functions is -- strongly recommended in preference to newForeignPtr with a -- finalizer. mallocForeignPtr :: Storable a => IO (ForeignPtr a) -- | This function is similar to mallocForeignPtr, except that the -- size of the memory required is given explicitly as a number of bytes. mallocForeignPtrBytes :: Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray0, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray0 :: Storable a => Int -> IO (ForeignPtr a) -- | Buffers used in the IO system module GHC.IO.Buffer -- | A mutable array of bytes that can be passed to foreign functions. -- -- The buffer is represented by a record, where the record contains the -- raw buffer and the start/end points of the filled portion. The buffer -- contents itself is mutable, but the rest of the record is immutable. -- This is a slightly odd mix, but it turns out to be quite practical: by -- making all the buffer metadata immutable, we can have operations on -- buffer metadata outside of the IO monad. -- -- The "live" elements of the buffer are those between the bufL -- and bufR offsets. In an empty buffer, bufL is equal to -- bufR, but they might not be zero: for example, the buffer might -- correspond to a memory-mapped file and in which case bufL will -- point to the next location to be written, which is not necessarily the -- beginning of the file. data Buffer e Buffer :: !RawBuffer e -> BufferState -> !Int -> !Int -> !Int -> Buffer e [bufRaw] :: Buffer e -> !RawBuffer e [bufState] :: Buffer e -> BufferState [bufSize] :: Buffer e -> !Int [bufL] :: Buffer e -> !Int [bufR] :: Buffer e -> !Int data BufferState ReadBuffer :: BufferState WriteBuffer :: BufferState type CharBuffer = Buffer Char type CharBufElem = Char newByteBuffer :: Int -> BufferState -> IO (Buffer Word8) newCharBuffer :: Int -> BufferState -> IO CharBuffer newBuffer :: Int -> Int -> BufferState -> IO (Buffer e) emptyBuffer :: RawBuffer e -> Int -> BufferState -> Buffer e bufferRemove :: Int -> Buffer e -> Buffer e bufferAdd :: Int -> Buffer e -> Buffer e -- | slides the contents of the buffer to the beginning slideContents :: Buffer Word8 -> IO (Buffer Word8) bufferAdjustL :: Int -> Buffer e -> Buffer e isEmptyBuffer :: Buffer e -> Bool isFullBuffer :: Buffer e -> Bool isFullCharBuffer :: Buffer e -> Bool isWriteBuffer :: Buffer e -> Bool bufferElems :: Buffer e -> Int bufferAvailable :: Buffer e -> Int summaryBuffer :: Buffer a -> String withBuffer :: Buffer e -> (Ptr e -> IO a) -> IO a withRawBuffer :: RawBuffer e -> (Ptr e -> IO a) -> IO a checkBuffer :: Buffer a -> IO () type RawBuffer e = ForeignPtr e readWord8Buf :: RawBuffer Word8 -> Int -> IO Word8 writeWord8Buf :: RawBuffer Word8 -> Int -> Word8 -> IO () type RawCharBuffer = RawBuffer CharBufElem peekCharBuf :: RawCharBuffer -> Int -> IO Char readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int) writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int) writeCharBufPtr :: Ptr CharBufElem -> Int -> Char -> IO Int charSize :: Int instance GHC.Classes.Eq GHC.IO.Buffer.BufferState -- | Types for text encoding/decoding module GHC.IO.Encoding.Types data BufferCodec from to state BufferCodec :: CodeBuffer from to -> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to)) -> IO () -> IO state -> (state -> IO ()) -> BufferCodec from to state -- | The encode function translates elements of the buffer -- from to the buffer to. It should translate as many -- elements as possible given the sizes of the buffers, including -- translating zero elements if there is either not enough room in -- to, or from does not contain a complete multibyte -- sequence. -- -- If multiple CodingProgress returns are possible, OutputUnderflow must -- be preferred to InvalidSequence. This allows GHC's IO library to -- assume that if we observe InvalidSequence there is at least a single -- element available in the output buffer. -- -- The fact that as many elements as possible are translated is used by -- the IO library in order to report translation errors at the point they -- actually occur, rather than when the buffer is translated. [encode] :: BufferCodec from to state -> CodeBuffer from to -- | The recover function is used to continue decoding in the -- presence of invalid or unrepresentable sequences. This includes both -- those detected by encode returning InvalidSequence -- and those that occur because the input byte sequence appears to be -- truncated. -- -- Progress will usually be made by skipping the first element of the -- from buffer. This function should only be called if you are -- certain that you wish to do this skipping and if the to -- buffer has at least one element of free space. Because this function -- deals with decoding failure, it assumes that the from buffer has at -- least one element. -- -- recover may raise an exception rather than skipping anything. -- -- Currently, some implementations of recover may mutate the -- input buffer. In particular, this feature is used to implement -- transliteration. [recover] :: BufferCodec from to state -> Buffer from -> Buffer to -> IO (Buffer from, Buffer to) -- | Resources associated with the encoding may now be released. The -- encode function may not be called again after calling -- close. [close] :: BufferCodec from to state -> IO () -- | Return the current state of the codec. -- -- Many codecs are not stateful, and in these case the state can be -- represented as '()'. Other codecs maintain a state. For example, -- UTF-16 recognises a BOM (byte-order-mark) character at the beginning -- of the input, and remembers thereafter whether to use big-endian or -- little-endian mode. In this case, the state of the codec would include -- two pieces of information: whether we are at the beginning of the -- stream (the BOM only occurs at the beginning), and if not, whether to -- use the big or little-endian encoding. [getState] :: BufferCodec from to state -> IO state [setState] :: BufferCodec from to state -> state -> IO () -- | A TextEncoding is a specification of a conversion scheme -- between sequences of bytes and sequences of Unicode characters. -- -- For example, UTF-8 is an encoding of Unicode characters into a -- sequence of bytes. The TextEncoding for UTF-8 is utf8. data TextEncoding TextEncoding :: String -> IO (TextDecoder dstate) -> IO (TextEncoder estate) -> TextEncoding -- | a string that can be passed to mkTextEncoding to create an -- equivalent TextEncoding. [textEncodingName] :: TextEncoding -> String -- | Creates a means of decoding bytes into characters: the result must not -- be shared between several byte sequences or simultaneously across -- threads [mkTextDecoder] :: TextEncoding -> IO (TextDecoder dstate) -- | Creates a means of encode characters into bytes: the result must not -- be shared between several character sequences or simultaneously across -- threads [mkTextEncoder] :: TextEncoding -> IO (TextEncoder estate) type TextEncoder state = BufferCodec CharBufElem Word8 state type TextDecoder state = BufferCodec Word8 CharBufElem state type CodeBuffer from to = Buffer from -> Buffer to -> IO (CodingProgress, Buffer from, Buffer to) type EncodeBuffer = CodeBuffer Char Word8 type DecodeBuffer = CodeBuffer Word8 Char data CodingProgress -- | Stopped because the input contains insufficient available elements, or -- all of the input sequence has been successfully translated. InputUnderflow :: CodingProgress -- | Stopped because the output contains insufficient free elements OutputUnderflow :: CodingProgress -- | Stopped because there are sufficient free elements in the output to -- output at least one encoded ASCII character, but the input contains an -- invalid or unrepresentable sequence InvalidSequence :: CodingProgress instance GHC.Show.Show GHC.IO.Encoding.Types.CodingProgress instance GHC.Classes.Eq GHC.IO.Encoding.Types.CodingProgress instance GHC.Show.Show GHC.IO.Encoding.Types.TextEncoding -- | Mutable references in the IO monad. module Data.IORef -- | A mutable variable in the IO monad data IORef a -- | Build a new IORef newIORef :: a -> IO (IORef a) -- | Read the value of an IORef readIORef :: IORef a -> IO a -- | Write a new value into an IORef writeIORef :: IORef a -> a -> IO () -- | Mutate the contents of an IORef. -- -- Be warned that modifyIORef does not apply the function -- strictly. This means if the program calls modifyIORef many -- times, but 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 modifyIORef' :: IORef a -> (a -> a) -> IO () -- | Atomically modifies the contents of an IORef. -- -- This function is useful for using IORef in a safe way in a -- multithreaded program. If you only have one IORef, then using -- atomicModifyIORef to access and modify it will prevent race -- conditions. -- -- Extending the atomicity to multiple IORefs is problematic, so -- it is recommended that if you need to do anything more complicated -- then using MVar instead is a good idea. -- -- atomicModifyIORef does not apply the function strictly. This is -- important to know even if all you are doing is replacing the value. -- For example, this will leak memory: -- --
-- ref <- newIORef '1' -- forever $ atomicModifyIORef ref (\_ -> ('2', ())) ---- -- Use atomicModifyIORef' or atomicWriteIORef to avoid this -- problem. atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b -- | Strict version of atomicModifyIORef. This forces both the value -- stored in the IORef and the value returned. The new value is -- installed in the IORef before the returned value is forced. So -- --
-- atomicModifyIORef' ref (x -> (x+1, undefined)) ---- -- will increment the IORef and then throw an exception in the -- calling thread. atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b -- | Variant of writeIORef with the "barrier to reordering" property -- that atomicModifyIORef has. atomicWriteIORef :: IORef a -> a -> IO () -- | Make a Weak pointer to an IORef, using the second -- argument as a finalizer to run when IORef is garbage-collected mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a)) -- | 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: -- --
-- '\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.Show.Show GHC.IO.Handle.Types.BufferMode instance GHC.Read.Read GHC.IO.Handle.Types.BufferMode instance GHC.Classes.Ord GHC.IO.Handle.Types.BufferMode instance GHC.Classes.Eq GHC.IO.Handle.Types.BufferMode instance GHC.Show.Show GHC.IO.Handle.Types.Newline instance GHC.Read.Read GHC.IO.Handle.Types.Newline instance GHC.Classes.Ord GHC.IO.Handle.Types.Newline instance GHC.Classes.Eq GHC.IO.Handle.Types.Newline instance GHC.Show.Show GHC.IO.Handle.Types.NewlineMode instance GHC.Read.Read GHC.IO.Handle.Types.NewlineMode instance GHC.Classes.Ord GHC.IO.Handle.Types.NewlineMode instance GHC.Classes.Eq GHC.IO.Handle.Types.NewlineMode instance GHC.Classes.Eq GHC.IO.Handle.Types.Handle instance GHC.Show.Show GHC.IO.Handle.Types.Handle instance GHC.Show.Show GHC.IO.Handle.Types.HandleType -- | 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: -- --
-- 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.Ord GHC.IO.Exception.AsyncException instance GHC.Classes.Eq GHC.IO.Exception.AsyncException instance GHC.Classes.Ord GHC.IO.Exception.ArrayException instance GHC.Classes.Eq GHC.IO.Exception.ArrayException instance GHC.Generics.Generic GHC.IO.Exception.ExitCode instance GHC.Show.Show GHC.IO.Exception.ExitCode instance GHC.Read.Read GHC.IO.Exception.ExitCode instance GHC.Classes.Ord GHC.IO.Exception.ExitCode instance GHC.Classes.Eq GHC.IO.Exception.ExitCode instance GHC.Exception.Type.Exception GHC.IO.Exception.IOException instance GHC.Classes.Eq GHC.IO.Exception.IOException instance GHC.Show.Show GHC.IO.Exception.IOException instance GHC.Classes.Eq GHC.IO.Exception.IOErrorType instance GHC.Show.Show GHC.IO.Exception.IOErrorType instance GHC.Exception.Type.Exception GHC.IO.Exception.ExitCode instance GHC.Exception.Type.Exception GHC.IO.Exception.FixIOException instance GHC.Show.Show GHC.IO.Exception.FixIOException instance GHC.Exception.Type.Exception GHC.IO.Exception.ArrayException instance GHC.Show.Show GHC.IO.Exception.ArrayException instance GHC.Exception.Type.Exception GHC.IO.Exception.AsyncException instance GHC.Show.Show GHC.IO.Exception.AsyncException instance GHC.Show.Show GHC.IO.Exception.SomeAsyncException instance GHC.Exception.Type.Exception GHC.IO.Exception.SomeAsyncException instance GHC.Exception.Type.Exception GHC.IO.Exception.AssertionFailed instance GHC.Show.Show GHC.IO.Exception.AssertionFailed instance GHC.Exception.Type.Exception GHC.IO.Exception.CompactionFailed instance GHC.Show.Show GHC.IO.Exception.CompactionFailed instance GHC.Exception.Type.Exception GHC.IO.Exception.AllocationLimitExceeded instance GHC.Show.Show GHC.IO.Exception.AllocationLimitExceeded instance GHC.Exception.Type.Exception GHC.IO.Exception.Deadlock instance GHC.Show.Show GHC.IO.Exception.Deadlock instance GHC.Exception.Type.Exception GHC.IO.Exception.BlockedIndefinitelyOnSTM instance GHC.Show.Show GHC.IO.Exception.BlockedIndefinitelyOnSTM instance GHC.Exception.Type.Exception GHC.IO.Exception.BlockedIndefinitelyOnMVar instance GHC.Show.Show GHC.IO.Exception.BlockedIndefinitelyOnMVar -- | Types for specifying how text encoding/decoding fails module GHC.IO.Encoding.Failure -- | The CodingFailureMode is used to construct -- TextEncodings, and specifies how they handle illegal sequences. data CodingFailureMode -- | Throw an error when an illegal sequence is encountered ErrorOnCodingFailure :: CodingFailureMode -- | Attempt to ignore and recover if an illegal sequence is encountered IgnoreCodingFailure :: CodingFailureMode -- | Replace with the closest visual match upon an illegal sequence TransliterateCodingFailure :: CodingFailureMode -- | Use the private-use escape mechanism to attempt to allow illegal -- sequences to be roundtripped. RoundtripFailure :: CodingFailureMode codingFailureModeSuffix :: CodingFailureMode -> String -- | Some characters are actually "surrogate" codepoints defined for use in -- UTF-16. We need to signal an invalid character if we detect them when -- encoding a sequence of Chars into Word8s because they -- won't give valid Unicode. -- -- We may also need to signal an invalid character if we detect them when -- encoding a sequence of Chars into Word8s because the -- RoundtripFailure mode creates these to round-trip bytes through -- our internal UTF-16 encoding. isSurrogate :: Char -> Bool recoverDecode :: CodingFailureMode -> Buffer Word8 -> Buffer Char -> IO (Buffer Word8, Buffer Char) recoverEncode :: CodingFailureMode -> Buffer Char -> Buffer Word8 -> IO (Buffer Char, Buffer Word8) instance GHC.Show.Show GHC.IO.Encoding.Failure.CodingFailureMode -- | UTF-8 Codec for the IO library -- -- Portions Copyright : (c) Tom Harper 2008-2009, (c) Bryan O'Sullivan -- 2009, (c) Duncan Coutts 2009 module GHC.IO.Encoding.UTF8 utf8 :: TextEncoding mkUTF8 :: CodingFailureMode -> TextEncoding utf8_bom :: TextEncoding mkUTF8_bom :: CodingFailureMode -> TextEncoding -- | UTF-32 Codecs for the IO library -- -- Portions Copyright : (c) Tom Harper 2008-2009, (c) Bryan O'Sullivan -- 2009, (c) Duncan Coutts 2009 module GHC.IO.Encoding.UTF32 utf32 :: TextEncoding mkUTF32 :: CodingFailureMode -> TextEncoding utf32_decode :: IORef (Maybe DecodeBuffer) -> DecodeBuffer utf32_encode :: IORef Bool -> EncodeBuffer utf32be :: TextEncoding mkUTF32be :: CodingFailureMode -> TextEncoding utf32be_decode :: DecodeBuffer utf32be_encode :: EncodeBuffer utf32le :: TextEncoding mkUTF32le :: CodingFailureMode -> TextEncoding utf32le_decode :: DecodeBuffer utf32le_encode :: EncodeBuffer -- | UTF-16 Codecs for the IO library -- -- Portions Copyright : (c) Tom Harper 2008-2009, (c) Bryan O'Sullivan -- 2009, (c) Duncan Coutts 2009 module GHC.IO.Encoding.UTF16 utf16 :: TextEncoding mkUTF16 :: CodingFailureMode -> TextEncoding utf16_decode :: IORef (Maybe DecodeBuffer) -> DecodeBuffer utf16_encode :: IORef Bool -> EncodeBuffer utf16be :: TextEncoding mkUTF16be :: CodingFailureMode -> TextEncoding utf16be_decode :: DecodeBuffer utf16be_encode :: EncodeBuffer utf16le :: TextEncoding mkUTF16le :: CodingFailureMode -> TextEncoding utf16le_decode :: DecodeBuffer utf16le_encode :: EncodeBuffer -- | Single-byte encodings that map directly to Unicode code points. -- -- Portions Copyright : (c) Tom Harper 2008-2009, (c) Bryan O'Sullivan -- 2009, (c) Duncan Coutts 2009 module GHC.IO.Encoding.Latin1 latin1 :: TextEncoding mkLatin1 :: CodingFailureMode -> TextEncoding latin1_checked :: TextEncoding mkLatin1_checked :: CodingFailureMode -> TextEncoding ascii :: TextEncoding mkAscii :: CodingFailureMode -> TextEncoding latin1_decode :: DecodeBuffer ascii_decode :: DecodeBuffer latin1_encode :: EncodeBuffer latin1_checked_encode :: EncodeBuffer ascii_encode :: EncodeBuffer -- | Routines for testing return values and raising a userError -- exception in case of values indicating an error state. module Foreign.Marshal.Error -- | Execute an IO action, throwing a userError if the -- predicate yields True when applied to the result returned by -- the IO action. If no exception is raised, return the result of -- the computation. throwIf :: (a -> Bool) -> (a -> String) -> IO a -> IO a -- | Like throwIf, but discarding the result throwIf_ :: (a -> Bool) -> (a -> String) -> IO a -> IO () -- | Guards against negative result values throwIfNeg :: (Ord a, Num a) => (a -> String) -> IO a -> IO a -- | Like throwIfNeg, but discarding the result throwIfNeg_ :: (Ord a, Num a) => (a -> String) -> IO a -> IO () -- | Guards against null pointers throwIfNull :: String -> IO (Ptr a) -> IO (Ptr a) -- | Discard the return value of an IO action -- | Deprecated: use void instead void :: IO a -> IO () -- | The module Foreign.Marshal.Alloc provides operations to -- allocate and deallocate blocks of raw memory (i.e., unstructured -- chunks of memory outside of the area maintained by the Haskell storage -- manager). These memory blocks are commonly used to pass compound data -- structures to foreign functions or to provide space in which compound -- result values are obtained from foreign functions. -- -- If any of the allocation functions fails, an exception is thrown. In -- some cases, memory exhaustion may mean the process is terminated. If -- free or reallocBytes is applied to a memory area that -- has been allocated with alloca or allocaBytes, the -- behaviour is undefined. Any further access to memory areas allocated -- with alloca or allocaBytes, after the computation that -- was passed to the allocation function has terminated, leads to -- undefined behaviour. Any further access to the memory area referenced -- by a pointer passed to realloc, reallocBytes, or -- free entails undefined behaviour. -- -- All storage allocated by functions that allocate based on a size in -- bytes must be sufficiently aligned for any of the basic foreign -- types that fits into the newly allocated storage. All storage -- allocated by functions that allocate based on a specific type must be -- sufficiently aligned for that type. Array allocation routines need to -- obey the same alignment constraints for each array element. module Foreign.Marshal.Alloc -- | alloca f executes the computation f, passing -- as argument a pointer to a temporarily allocated block of memory -- sufficient to hold values of type a. -- -- The memory is freed when f terminates (either normally or via -- an exception), so the pointer passed to f must not be -- used after this. alloca :: forall a b. Storable a => (Ptr a -> IO b) -> IO b -- | allocaBytes n f executes the computation f, -- passing as argument a pointer to a temporarily allocated block of -- memory of n bytes. The block of memory is sufficiently -- aligned for any of the basic foreign types that fits into a memory -- block of the allocated size. -- -- The memory is freed when f terminates (either normally or via -- an exception), so the pointer passed to f must not be -- used after this. allocaBytes :: Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b -- | Allocate a block of memory that is sufficient to hold values of type -- a. The size of the area allocated is determined by the -- sizeOf method from the instance of Storable for the -- appropriate type. -- -- The memory may be deallocated using free or -- finalizerFree when no longer required. malloc :: forall a. 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 :: forall a. Storable a => IO (Ptr a) -- | Llike mallocBytes but memory is filled with bytes of value -- zero. callocBytes :: Int -> IO (Ptr a) -- | Resize a memory area that was allocated with malloc or -- mallocBytes to the size needed to store values of type -- b. The returned pointer may refer to an entirely different -- memory area, but will be suitably aligned to hold values of type -- b. The contents of the referenced memory area will be the -- same as of the original pointer up to the minimum of the original size -- and the size of values of type b. -- -- If the argument to realloc is nullPtr, realloc -- behaves like malloc. realloc :: 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 :: forall a. 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 :: forall a b. 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 :: forall a. 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 :: forall a. 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 :: forall a. 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 :: forall a. 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 :: forall a. Storable a => Ptr a -> Int -> Ptr a -- | Foreign marshalling support for CStrings with configurable encodings module GHC.Foreign -- | Marshal a NUL terminated C string into a Haskell string. peekCString :: TextEncoding -> CString -> IO String -- | Marshal a C string with explicit length into a Haskell string. peekCStringLen :: TextEncoding -> CStringLen -> IO String -- | Marshal a Haskell string into a NUL terminated C string. -- --
-- toDyn (id :: Int -> Int) --toDyn :: Typeable a => a -> Dynamic -- | Converts a Dynamic object back into an ordinary Haskell value -- of the correct type. See also fromDynamic. fromDyn :: Typeable a => Dynamic -> a -> a -- | Converts a Dynamic object back into an ordinary Haskell value -- of the correct type. See also fromDyn. fromDynamic :: forall a. Typeable a => Dynamic -> Maybe a dynApply :: Dynamic -> Dynamic -> Maybe Dynamic dynApp :: Dynamic -> Dynamic -> Dynamic dynTypeRep :: Dynamic -> SomeTypeRep -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable (a :: k) instance GHC.Show.Show Data.Dynamic.Dynamic instance GHC.Exception.Type.Exception Data.Dynamic.Dynamic -- | Basic concurrency stuff. module GHC.Conc.Sync -- | A ThreadId is an abstract type representing a handle to a -- thread. ThreadId is an instance of Eq, Ord and -- Show, where the Ord instance implements an arbitrary -- total ordering over ThreadIds. The Show instance lets -- you convert an arbitrary-valued ThreadId to string form; -- showing a ThreadId value is occasionally useful when debugging -- or diagnosing the behaviour of a concurrent program. -- -- Note: in GHC, if you have a ThreadId, you essentially -- have a pointer to the thread itself. This means the thread itself -- can't be garbage collected until you drop the ThreadId. This -- misfeature will hopefully be corrected at a later date. data ThreadId ThreadId :: ThreadId# -> ThreadId -- | Creates a new thread to run the IO computation passed as the -- first argument, and returns the ThreadId of the newly created -- thread. -- -- The new thread will be a lightweight, unbound thread. Foreign -- calls made by this thread are not guaranteed to be made by any -- particular OS thread; if you need foreign calls to be made by a -- particular OS thread, then use forkOS instead. -- -- The new thread inherits the masked state of the parent (see -- mask). -- -- The newly created thread has an exception handler that discards the -- exceptions BlockedIndefinitelyOnMVar, -- BlockedIndefinitelyOnSTM, and ThreadKilled, and passes -- all other exceptions to the uncaught exception handler. forkIO :: IO () -> IO ThreadId -- | Like forkIO, but the child thread is passed a function that can -- be used to unmask asynchronous exceptions. This function is typically -- used in the following way -- --
-- ... mask_ $ forkIOWithUnmask $ \unmask -> -- catch (unmask ...) handler ---- -- so that the exception handler in the child thread is established with -- asynchronous exceptions masked, meanwhile the main body of the child -- thread is executed in the unmasked state. -- -- Note that the unmask function passed to the child thread should only -- be used in that thread; the behaviour is undefined if it is invoked in -- a different thread. forkIOWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | Like forkIO, but lets you specify on which capability the -- thread should run. Unlike a forkIO thread, a thread created by -- forkOn will stay on the same capability for its entire lifetime -- (forkIO threads can migrate between capabilities according to -- the scheduling policy). forkOn is useful for overriding the -- scheduling policy when you know in advance how best to distribute the -- threads. -- -- The Int argument specifies a capability number (see -- getNumCapabilities). Typically capabilities correspond to -- physical processors, but the exact behaviour is -- implementation-dependent. The value passed to forkOn is -- interpreted modulo the total number of capabilities as returned by -- getNumCapabilities. -- -- GHC note: the number of capabilities is specified by the +RTS -- -N option when the program is started. Capabilities can be fixed -- to actual processor cores with +RTS -qa if the underlying -- operating system supports that, although in practice this is usually -- unnecessary (and may actually degrade performance in some cases - -- experimentation is recommended). forkOn :: Int -> IO () -> IO ThreadId -- | Like forkIOWithUnmask, but the child thread is pinned to the -- given CPU, as with forkOn. forkOnWithUnmask :: Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | the value passed to the +RTS -N flag. This is the number of -- Haskell threads that can run truly simultaneously at any given time, -- and is typically set to the number of physical processor cores on the -- machine. -- -- Strictly speaking it is better to use getNumCapabilities, -- because the number of capabilities might vary at runtime. numCapabilities :: Int -- | Returns the number of Haskell threads that can run truly -- simultaneously (on separate physical processors) at any given time. To -- change this value, use setNumCapabilities. getNumCapabilities :: IO Int -- | Set the number of Haskell threads that can run truly simultaneously -- (on separate physical processors) at any given time. The number passed -- to forkOn is interpreted modulo this value. The initial value -- is given by the +RTS -N runtime flag. -- -- This is also the number of threads that will participate in parallel -- garbage collection. It is strongly recommended that the number of -- capabilities is not set larger than the number of physical processor -- cores, and it may often be beneficial to leave one or more cores free -- to avoid contention with other processes in the machine. setNumCapabilities :: Int -> IO () -- | Returns the number of CPUs that the machine has getNumProcessors :: IO Int -- | Returns the number of sparks currently in the local spark pool numSparks :: IO Int childHandler :: SomeException -> IO () -- | Returns the ThreadId of the calling thread (GHC only). myThreadId :: IO ThreadId -- | killThread raises the ThreadKilled exception in the -- given thread (GHC only). -- --
-- killThread tid = throwTo tid ThreadKilled --killThread :: ThreadId -> IO () -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- Exception delivery synchronizes between the source and target thread: -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. Exception delivery is also -- atomic with respect to other exceptions. Atomicity is a useful -- property to have when dealing with race conditions: e.g. if there are -- two threads that can kill each other, it is guaranteed that only one -- of the threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () par :: a -> b -> b infixr 0 `par` pseq :: a -> b -> b infixr 0 `pseq` -- | Internal function used by the RTS to run sparks. runSparks :: IO () -- | The yield action allows (forces, in a co-operative multitasking -- implementation) a context-switch to any other currently runnable -- threads (if any), and is occasionally useful when implementing -- concurrency abstractions. yield :: IO () -- | labelThread stores a string as identifier for this thread if -- you built a RTS with debugging support. This identifier will be used -- in the debugging output to make distinction of different threads -- easier (otherwise you only have the thread state object's address in -- the heap). -- -- Other applications like the graphical Concurrent Haskell Debugger -- (http://www.informatik.uni-kiel.de/~fhu/chd/) may choose to -- overload labelThread for their purposes as well. labelThread :: ThreadId -> String -> IO () -- | Make a weak pointer to a ThreadId. It can be important to do -- this if you want to hold a reference to a ThreadId while still -- allowing the thread to receive the BlockedIndefinitely family -- of exceptions (e.g. BlockedIndefinitelyOnMVar). Holding a -- normal ThreadId reference will prevent the delivery of -- BlockedIndefinitely exceptions because the reference could be -- used as the target of throwTo at any time, which would unblock -- the thread. -- -- Holding a Weak ThreadId, on the other hand, will not prevent -- the thread from receiving BlockedIndefinitely exceptions. It -- is still possible to throw an exception to a Weak ThreadId, -- but the caller must use deRefWeak first to determine whether -- the thread still exists. mkWeakThreadId :: ThreadId -> IO (Weak ThreadId) -- | The current status of a thread data ThreadStatus -- | the thread is currently runnable or running ThreadRunning :: ThreadStatus -- | the thread has finished ThreadFinished :: ThreadStatus -- | the thread is blocked on some resource ThreadBlocked :: BlockReason -> ThreadStatus -- | the thread received an uncaught exception ThreadDied :: ThreadStatus data BlockReason -- | blocked on MVar BlockedOnMVar :: BlockReason -- | blocked on a computation in progress by another thread BlockedOnBlackHole :: BlockReason -- | blocked in throwTo BlockedOnException :: BlockReason -- | blocked in retry in an STM transaction BlockedOnSTM :: BlockReason -- | currently in a foreign call BlockedOnForeignCall :: BlockReason -- | blocked on some other resource. Without -threaded, I/O and -- threadDelay show up as BlockedOnOther, with -- -threaded they show up as BlockedOnMVar. BlockedOnOther :: BlockReason threadStatus :: ThreadId -> IO ThreadStatus -- | Returns the number of the capability on which the thread is currently -- running, and a boolean indicating whether the thread is locked to that -- capability or not. A thread is locked to a capability if it was -- created with forkOn. threadCapability :: ThreadId -> IO (Int, Bool) -- | Make a StablePtr that can be passed to the C function -- hs_try_putmvar(). The RTS wants a StablePtr to the -- underlying MVar#, but a StablePtr# can only refer to -- lifted types, so we have to cheat by coercing. newStablePtrPrimMVar :: MVar () -> IO (StablePtr PrimMVar) data PrimMVar -- | Every thread has an allocation counter that tracks how much memory has -- been allocated by the thread. The counter is initialized to zero, and -- setAllocationCounter sets the current value. The allocation -- counter counts *down*, so in the absence of a call to -- setAllocationCounter its value is the negation of the number of -- bytes of memory allocated by the thread. -- -- There are two things that you can do with this counter: -- --
-- 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. -- --
-- 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: -- --
-- throw e `seq` x ===> throw e -- throwIO e `seq` x ===> x ---- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwIO will only cause -- an exception to be raised when it is used within the IO monad. -- The throwIO variant should be used in preference to -- throw to raise an exception within the IO monad because -- it guarantees ordering with respect to other IO operations, -- whereas throw does not. throwIO :: Exception e => e -> IO a -- | Throw an exception. Exceptions may be thrown from purely functional -- code, but may only be caught within the IO monad. throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e. Exception e => e -> a -- | Raise an IOException 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 a the opposite behaviour. This is ok, -- because catch is an IO computation. catch :: Exception e => IO a -> (e -> IO a) -> IO a -- | The function catchJust is like catch, but it takes an -- extra argument which is an exception predicate, a function -- which selects which type of exceptions we're interested in. -- --
-- catchJust (\e -> if isDoesNotExistErrorType (ioeGetErrorType e) then Just () else Nothing) -- (readFile f) -- (\_ -> do hPutStrLn stderr ("No such file: " ++ show f) -- return "") ---- -- Any other exceptions which are not matched by the predicate are -- re-raised, and may be caught by an enclosing catch, -- catchJust, etc. catchJust :: Exception e => (e -> Maybe b) -> IO a -> (b -> IO a) -> IO a -- | A version of catch with the arguments swapped around; useful in -- situations where the code for the handler is shorter. For example: -- --
-- do handle (\NonTermination -> exitWith (ExitFailure 1)) $ -- ... --handle :: Exception e => (e -> IO a) -> IO a -> IO a -- | A version of catchJust with the arguments swapped around (see -- handle). handleJust :: Exception e => (e -> Maybe b) -> (b -> IO a) -> IO a -> IO a -- | Similar to catch, but returns an Either result which is -- (Right a) if no exception of type e was -- raised, or (Left ex) if an exception of type -- e was raised and its value is ex. If any other type -- of exception is raised 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 :: 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 runtimeError :: Addr# -> a nonExhaustiveGuardsError :: Addr# -> a patError :: Addr# -> a noMethodBindingError :: Addr# -> a absentError :: Addr# -> a typeError :: Addr# -> a nonTermination :: SomeException nestedAtomically :: SomeException instance GHC.Show.Show Control.Exception.Base.NestedAtomically instance GHC.Exception.Type.Exception Control.Exception.Base.NestedAtomically instance GHC.Show.Show Control.Exception.Base.NonTermination instance GHC.Exception.Type.Exception Control.Exception.Base.NonTermination instance GHC.Show.Show Control.Exception.Base.TypeError instance GHC.Exception.Type.Exception Control.Exception.Base.TypeError instance GHC.Show.Show Control.Exception.Base.NoMethodError instance GHC.Exception.Type.Exception Control.Exception.Base.NoMethodError instance GHC.Show.Show Control.Exception.Base.RecUpdError instance GHC.Exception.Type.Exception Control.Exception.Base.RecUpdError instance GHC.Show.Show Control.Exception.Base.RecConError instance GHC.Exception.Type.Exception Control.Exception.Base.RecConError instance GHC.Show.Show Control.Exception.Base.RecSelError instance GHC.Exception.Type.Exception Control.Exception.Base.RecSelError instance GHC.Show.Show Control.Exception.Base.PatternMatchFail instance GHC.Exception.Type.Exception Control.Exception.Base.PatternMatchFail -- | Standard IO Errors. module System.IO.Error -- | The Haskell 2010 type for exceptions in the IO monad. Any I/O -- operation may raise an IOException 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 IOException 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 IOException 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 IOException. If any of the file handle or file path is not -- given the corresponding value in the IOException 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 -- IOException. 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 IOException in the IO monad. ioError :: IOError -> IO a -- | The catchIOError function establishes a handler that receives -- any IOException raised in the action protected by -- catchIOError. An IOException is caught by the most -- recent handler established by one of the exception handling functions. -- These handlers are not selective: all IOExceptions 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 IOException 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 IOException 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: -- --
-- 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: -- --
-- throw e `seq` x ===> throw e -- throwIO e `seq` x ===> x ---- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwIO will only cause -- an exception to be raised when it is used within the IO monad. -- The throwIO variant should be used in preference to -- throw to raise an exception within the IO monad because -- it guarantees ordering with respect to other IO operations, -- whereas throw does not. throwIO :: Exception e => e -> IO a -- | Raise an IOException 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 a the opposite behaviour. This is ok, -- because catch is an IO computation. catch :: Exception e => IO a -> (e -> IO a) -> IO a -- | Sometimes you want to catch two different sorts of exception. You -- could do something like -- --
-- f = expr `catch` \ (ex :: ArithException) -> handleArith ex -- `catch` \ (ex :: IOException) -> handleIO ex ---- -- However, there are a couple of problems with this approach. The first -- is that having two exception handlers is inefficient. However, the -- more serious issue is that the second exception handler will catch -- exceptions in the first, e.g. in the example above, if -- handleArith throws an IOException then the second -- exception handler will catch it. -- -- Instead, we provide a function catches, which would be used -- thus: -- --
-- f = expr `catches` [Handler (\ (ex :: ArithException) -> handleArith ex), -- Handler (\ (ex :: IOException) -> handleIO ex)] --catches :: IO a -> [Handler a] -> IO a -- | You need this when using catches. data Handler a Handler :: (e -> IO a) -> Handler a -- | The function catchJust is like catch, but it takes an -- extra argument which is an exception predicate, a function -- which selects which type of exceptions we're interested in. -- --
-- catchJust (\e -> if isDoesNotExistErrorType (ioeGetErrorType e) then Just () else Nothing) -- (readFile f) -- (\_ -> do hPutStrLn stderr ("No such file: " ++ show f) -- return "") ---- -- Any other exceptions which are not matched by the predicate are -- re-raised, and may be caught by an enclosing catch, -- catchJust, etc. catchJust :: Exception e => (e -> Maybe b) -> IO a -> (b -> IO a) -> IO a -- | A version of catch with the arguments swapped around; useful in -- situations where the code for the handler is shorter. For example: -- --
-- do handle (\NonTermination -> exitWith (ExitFailure 1)) $ -- ... --handle :: Exception e => (e -> IO a) -> IO a -> IO a -- | A version of catchJust with the arguments swapped around (see -- handle). handleJust :: Exception e => (e -> Maybe b) -> (b -> IO a) -> IO a -> IO a -- | Similar to catch, but returns an Either result which is -- (Right a) if no exception of type e was -- raised, or (Left ex) if an exception of type -- e was raised and its value is ex. If any other type -- of exception is raised 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 :: 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: -- --
-- test :: IORef [a] -- test = unsafePerformIO $ newIORef [] -- -- main = do -- writeIORef test [42] -- bang <- readIORef test -- print (bang :: [Char]) ---- -- This program will core dump. This problem with polymorphic references -- is well known in the ML community, and does not arise with normal -- monadic use of references. There is no easy way to make it impossible -- once you use unsafePerformIO. Indeed, it is possible to write -- coerce :: a -> b with the help of unsafePerformIO. -- So be careful! unsafePerformIO :: IO a -> a -- | This version of unsafePerformIO is more efficient because it -- omits the check that the IO is only being performed by a single -- thread. Hence, when you use unsafeDupablePerformIO, there is a -- possibility that the IO action may be performed multiple times (on a -- multiprocessor), and you should therefore ensure that it gives the -- same results each time. It may even happen that one of the duplicated -- IO actions is only run partially, and then interrupted in the middle -- without an exception being raised. Therefore, functions like -- bracket cannot be used safely within -- unsafeDupablePerformIO. unsafeDupablePerformIO :: IO a -> a -- | unsafeInterleaveIO allows an IO computation to be -- deferred lazily. When passed a value of type IO a, the -- IO will only be performed when the value of the a is -- demanded. This is used to implement lazy file reading, see -- hGetContents. unsafeInterleaveIO :: IO a -> IO a -- | A slightly faster version of fixIO that may not be safe to use -- with multiple threads. The unsafety arises when used like this: -- --
-- unsafeFixIO $ \r -> do -- forkIO (print r) -- return (...) ---- -- In this case, the child thread will receive a NonTermination -- exception instead of waiting for the value of r to be -- computed. unsafeFixIO :: (a -> IO a) -> IO a -- | 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 -> IO (Buffer from, Buffer to)) -> IO () -> IO state -> (state -> IO ()) -> BufferCodec from to state -- | The encode function translates elements of the buffer -- from to the buffer to. It should translate as many -- elements as possible given the sizes of the buffers, including -- translating zero elements if there is either not enough room in -- to, or from does not contain a complete multibyte -- sequence. -- -- If multiple CodingProgress returns are possible, OutputUnderflow must -- be preferred to InvalidSequence. This allows GHC's IO library to -- assume that if we observe InvalidSequence there is at least a single -- element available in the output buffer. -- -- The fact that as many elements as possible are translated is used by -- the IO library in order to report translation errors at the point they -- actually occur, rather than when the buffer is translated. [encode] :: BufferCodec from to state -> CodeBuffer from to -- | The recover function is used to continue decoding in the -- presence of invalid or unrepresentable sequences. This includes both -- those detected by encode returning InvalidSequence -- and those that occur because the input byte sequence appears to be -- truncated. -- -- Progress will usually be made by skipping the first element of the -- from buffer. This function should only be called if you are -- certain that you wish to do this skipping and if the to -- buffer has at least one element of free space. Because this function -- deals with decoding failure, it assumes that the from buffer has at -- least one element. -- -- recover may raise an exception rather than skipping anything. -- -- Currently, some implementations of recover may mutate the -- input buffer. In particular, this feature is used to implement -- transliteration. [recover] :: BufferCodec from to state -> Buffer from -> Buffer to -> IO (Buffer from, Buffer to) -- | Resources associated with the encoding may now be released. The -- encode function may not be called again after calling -- close. [close] :: BufferCodec from to state -> IO () -- | Return the current state of the codec. -- -- Many codecs are not stateful, and in these case the state can be -- represented as '()'. Other codecs maintain a state. For example, -- UTF-16 recognises a BOM (byte-order-mark) character at the beginning -- of the input, and remembers thereafter whether to use big-endian or -- little-endian mode. In this case, the state of the codec would include -- two pieces of information: whether we are at the beginning of the -- stream (the BOM only occurs at the beginning), and if not, whether to -- use the big or little-endian encoding. [getState] :: BufferCodec from to state -> IO state [setState] :: BufferCodec from to state -> state -> IO () -- | A TextEncoding is a specification of a conversion scheme -- between sequences of bytes and sequences of Unicode characters. -- -- For example, UTF-8 is an encoding of Unicode characters into a -- sequence of bytes. The TextEncoding for UTF-8 is utf8. data TextEncoding TextEncoding :: String -> IO (TextDecoder dstate) -> IO (TextEncoder estate) -> TextEncoding -- | a string that can be passed to mkTextEncoding to create an -- equivalent TextEncoding. [textEncodingName] :: TextEncoding -> String -- | Creates a means of decoding bytes into characters: the result must not -- be shared between several byte sequences or simultaneously across -- threads [mkTextDecoder] :: TextEncoding -> IO (TextDecoder dstate) -- | Creates a means of encode characters into bytes: the result must not -- be shared between several character sequences or simultaneously across -- threads [mkTextEncoder] :: TextEncoding -> IO (TextEncoder estate) type TextEncoder state = BufferCodec CharBufElem Word8 state type TextDecoder state = BufferCodec Word8 CharBufElem state data CodingProgress -- | Stopped because the input contains insufficient available elements, or -- all of the input sequence has been successfully translated. InputUnderflow :: CodingProgress -- | Stopped because the output contains insufficient free elements OutputUnderflow :: CodingProgress -- | Stopped because there are sufficient free elements in the output to -- output at least one encoded ASCII character, but the input contains an -- invalid or unrepresentable sequence InvalidSequence :: CodingProgress -- | The Latin1 (ISO8859-1) encoding. This encoding maps bytes directly to -- the first 256 Unicode code points, and is thus not a complete Unicode -- encoding. An attempt to write a character greater than '\255' -- to a Handle using the latin1 encoding will result in an -- error. latin1 :: TextEncoding latin1_encode :: CharBuffer -> Buffer Word8 -> IO (CharBuffer, Buffer Word8) latin1_decode :: Buffer Word8 -> CharBuffer -> IO (Buffer Word8, CharBuffer) -- | The UTF-8 Unicode encoding utf8 :: TextEncoding -- | The UTF-8 Unicode encoding, with a byte-order-mark (BOM; the byte -- sequence 0xEF 0xBB 0xBF). This encoding behaves like utf8, -- except that on input, the BOM sequence is ignored at the beginning of -- the stream, and on output, the BOM sequence is prepended. -- -- The byte-order-mark is strictly unnecessary in UTF-8, but is sometimes -- used to identify the encoding of a file. utf8_bom :: TextEncoding -- | The UTF-16 Unicode encoding (a byte-order-mark should be used to -- indicate endianness). utf16 :: TextEncoding -- | The UTF-16 Unicode encoding (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 Unicode encoding of the current locale, but allowing arbitrary -- undecodable bytes to be round-tripped through it. -- -- This TextEncoding is used to decode and encode command line -- arguments and environment variables on non-Windows platforms. -- -- On Windows, this encoding *should not* be used if possible because the -- use of code pages is deprecated: Strings should be retrieved via the -- "wide" W-family of UTF-16 APIs instead getFileSystemEncoding :: IO TextEncoding -- | The Unicode encoding of the current locale, but where undecodable -- bytes are replaced with their closest visual match. Used for the -- CString marshalling functions in Foreign.C.String getForeignEncoding :: IO TextEncoding setLocaleEncoding :: TextEncoding -> IO () setFileSystemEncoding :: TextEncoding -> IO () setForeignEncoding :: TextEncoding -> IO () -- | An encoding in which Unicode code points are translated to bytes by -- taking the code point modulo 256. When decoding, bytes are translated -- directly into the equivalent code point. -- -- This encoding never fails in either direction. However, encoding -- discards information, so encode followed by decode is not the -- identity. char8 :: TextEncoding -- | Look up the named Unicode encoding. May fail with -- --
UTF-8
-- 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>:2:1 in interactive:Ghci1 ---- -- GHC solves HasCallStack constraints in three steps: -- --
-- 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 -- | 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 :: (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 :: (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> IOMode -> Maybe TextEncoding -> NewlineMode -> IO Handle -- | like mkFileHandle, except that a Handle is created with -- two independent buffers, one for reading and one for writing. Used for -- full-duplex streams, such as network sockets. mkDuplexHandle :: (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle 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 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 () module GHC.Environment -- | Computation getFullArgs is the "raw" version of getArgs, -- similar to argv in other languages. It returns a list of the -- program's command line arguments, starting with the program name, and -- including those normally eaten by the RTS (+RTS ... -RTS). getFullArgs :: IO [String] -- | An MVar t is mutable location that is either empty or -- contains a value of type t. It has two fundamental -- operations: putMVar which fills an MVar if it is empty -- and blocks otherwise, and takeMVar which empties an MVar -- if it is full and blocks otherwise. They can be used in multiple -- different ways: -- --
-- 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: -- --
-- readMVar :: MVar a -> IO a -- readMVar m = -- mask_ $ do -- a <- takeMVar m -- putMVar m a -- return a --readMVar :: MVar a -> IO a -- | Take a value from an MVar, put a new value into the MVar -- and return the value taken. This function is atomic only if there are -- no other producers for this MVar. swapMVar :: MVar a -> a -> IO a -- | A non-blocking version of takeMVar. The tryTakeMVar -- function returns immediately, with Nothing if the MVar -- was empty, or Just a if the MVar was full with -- contents a. After tryTakeMVar, the MVar is left -- empty. tryTakeMVar :: MVar a -> IO (Maybe a) -- | A non-blocking version of putMVar. The tryPutMVar -- function attempts to put the value a into the MVar, -- returning True if it was successful, or False otherwise. tryPutMVar :: MVar a -> a -> IO Bool -- | Check whether a given MVar is empty. -- -- Notice that the boolean value returned is just a snapshot of the state -- of the MVar. By the time you get to react on its result, the MVar may -- have been filled (or emptied) - so be extremely careful when using -- this operation. Use tryTakeMVar instead if possible. isEmptyMVar :: MVar a -> IO Bool -- | withMVar is an exception-safe wrapper for operating on the -- contents of an MVar. This operation is exception-safe: it will -- replace the original contents of the MVar if an exception is -- raised (see Control.Exception). However, it is only atomic if -- there are no other producers for this MVar. withMVar :: MVar a -> (a -> IO b) -> IO b -- | Like withMVar, but the IO action in the second -- argument is executed with asynchronous exceptions masked. withMVarMasked :: MVar a -> (a -> IO b) -> IO b -- | An exception-safe wrapper for modifying the contents of an -- MVar. Like withMVar, modifyMVar will replace the -- original contents of the MVar if an exception is raised during -- the operation. This function is only atomic if there are no other -- producers for this MVar. modifyMVar_ :: MVar a -> (a -> IO a) -> IO () -- | A slight variation on modifyMVar_ that allows a value to be -- returned (b) in addition to the modified value of the -- MVar. modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b -- | Like modifyMVar_, but the IO action in the second -- argument is executed with asynchronous exceptions masked. modifyMVarMasked_ :: MVar a -> (a -> IO a) -> IO () -- | Like modifyMVar, but the IO action in the second -- argument is executed with asynchronous exceptions masked. modifyMVarMasked :: MVar a -> (a -> IO (a, b)) -> IO b -- | A non-blocking version of readMVar. The tryReadMVar -- function returns immediately, with Nothing if the MVar -- was empty, or Just a if the MVar was full with -- contents a. tryReadMVar :: MVar a -> IO (Maybe a) -- | Make a Weak pointer to an MVar, using the second -- argument as a finalizer to run when MVar is garbage-collected mkWeakMVar :: MVar a -> IO () -> IO (Weak (MVar a)) -- | Deprecated: use mkWeakMVar instead addMVarFinalizer :: MVar a -> IO () -> IO () module GHC.Conc.Signal type Signal = CInt type HandlerFun = ForeignPtr Word8 -> IO () setHandler :: Signal -> Maybe (HandlerFun, Dynamic) -> IO (Maybe (HandlerFun, Dynamic)) runHandlers :: ForeignPtr Word8 -> Signal -> IO () runHandlersPtr :: Ptr Word8 -> Signal -> IO () -- | Basic concurrency stuff. module GHC.Conc.IO ensureIOManagerIsRunning :: IO () ioManagerCapabilitiesChanged :: IO () -- | Suspends the current thread for a given number of microseconds (GHC -- only). -- -- There is no guarantee that the thread will be rescheduled promptly -- when the delay has expired, but the thread will never continue to run -- earlier than specified. threadDelay :: Int -> IO () -- | 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. 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. 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.Show.Show GHC.IO.FD.FD instance GHC.IO.Device.RawIO GHC.IO.FD.FD instance GHC.IO.Device.IODevice GHC.IO.FD.FD instance GHC.IO.BufferedIO.BufferedIO GHC.IO.FD.FD -- | 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: -- --
-- do h <- openFile "mystdout" WriteMode -- hDuplicateTo h stdout --hDuplicateTo :: Handle -> Handle -> IO () -- | Computation hClose hdl makes handle hdl -- closed. Before the computation finishes, if hdl is writable -- its buffer is flushed as for hFlush. Performing hClose -- on a handle that has already been closed has no effect; doing so is -- not an error. All other operations on a closed handle will fail. If -- hClose fails for any reason, any further operations (apart from -- hClose) on the handle will still fail as if hdl had -- been successfully closed. hClose :: Handle -> IO () hClose_help :: Handle__ -> IO (Handle__, Maybe SomeException) -- | Indicates a mode in which a file should be locked. data LockMode SharedLock :: LockMode ExclusiveLock :: LockMode -- | If a Handle references a file descriptor, attempt to lock -- contents of the underlying file in appropriate mode. If the file is -- already locked in incompatible mode, this function blocks until the -- lock is established. The lock is automatically released upon closing a -- Handle. -- -- Things to be aware of: -- -- 1) This function may block inside a C call. If it does, in order to be -- able to interrupt it with asynchronous exceptions and/or for other -- threads to continue working, you MUST use threaded version of the -- runtime system. -- -- 2) The implementation uses LockFileEx on Windows and -- flock otherwise, hence all of their caveats also apply here. -- -- 3) On non-Windows 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. 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: -- --
-- '\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: -- --
-- main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]]) --appendFile :: FilePath -> String -> IO () -- | For a handle hdl which attached to a physical file, -- hFileSize hdl returns the size of that file in 8-bit -- bytes. hFileSize :: Handle -> IO Integer -- | hSetFileSize hdl size truncates the physical -- file with handle hdl to size bytes. hSetFileSize :: Handle -> Integer -> IO () -- | For a readable handle hdl, hIsEOF hdl returns -- True if no further input can be taken from hdl or for -- a physical file, if the current I/O position is equal to the length of -- the file. Otherwise, it returns False. -- -- NOTE: hIsEOF may block, because it has to attempt to read from -- the stream to determine whether there is any more data to be read. hIsEOF :: Handle -> IO Bool -- | The computation isEOF is identical to hIsEOF, except -- that it works only on stdin. isEOF :: IO Bool -- | Three kinds of buffering are supported: line-buffering, -- block-buffering or no-buffering. These modes have the following -- effects. For output, items are written out, or flushed, from -- the internal buffer according to the buffer mode: -- --
-- main = print ([(n, 2^n) | n <- [0..19]]) --print :: Show a => a -> IO () -- | Read a character from the standard input device (same as -- hGetChar stdin). getChar :: IO Char -- | Read a line from the standard input device (same as hGetLine -- stdin). getLine :: IO String -- | The getContents operation returns all user input as a single -- string, which is read lazily as it is needed (same as -- hGetContents stdin). getContents :: IO String -- | The 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 name mode act opens a file using -- openBinaryFile and passes the resulting handle to the -- computation act. The handle will be closed on exit from -- withBinaryFile, whether by normal termination or by raising an -- exception. withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r -- | Like openFile, but open the file in binary mode. On Windows, -- reading a file in text mode (which is the default) will translate CRLF -- to LF, and writing will translate LF to CRLF. This is usually what you -- want with text files. With binary files this is undesirable; also, as -- usual under Microsoft operating systems, text mode treats control-Z as -- EOF. Binary mode turns off all special treatment of end-of-line and -- end-of-file characters. (See also hSetBinaryMode.) openBinaryFile :: FilePath -> IOMode -> IO Handle -- | Select binary mode (True) or text mode (False) on a open -- handle. (See also openBinaryFile.) -- -- This has the same effect as calling hSetEncoding with -- char8, together with hSetNewlineMode with -- noNewlineTranslation. hSetBinaryMode :: Handle -> Bool -> IO () -- | hPutBuf hdl buf count writes count 8-bit -- bytes from the buffer buf to the handle hdl. It -- returns (). -- -- hPutBuf ignores any text encoding that applies to the -- Handle, writing the bytes directly to the underlying file or -- device. -- -- hPutBuf ignores the prevailing TextEncoding and -- NewlineMode on the Handle, and writes bytes directly. -- -- This operation may fail with: -- --
UTF-8
-- '\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: -- --
-- >>> 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, -- --
-- >>> fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5 -- 120 ---- -- 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 :: (a -> a) -> a instance Control.Monad.Fix.MonadFix GHC.Maybe.Maybe instance Control.Monad.Fix.MonadFix [] instance Control.Monad.Fix.MonadFix GHC.Base.NonEmpty instance Control.Monad.Fix.MonadFix GHC.Types.IO instance Control.Monad.Fix.MonadFix ((->) r) instance Control.Monad.Fix.MonadFix (Data.Either.Either e) instance Control.Monad.Fix.MonadFix (GHC.ST.ST s) instance Control.Monad.Fix.MonadFix Data.Semigroup.Internal.Dual instance Control.Monad.Fix.MonadFix Data.Semigroup.Internal.Sum instance Control.Monad.Fix.MonadFix Data.Semigroup.Internal.Product instance Control.Monad.Fix.MonadFix Data.Monoid.First instance Control.Monad.Fix.MonadFix Data.Monoid.Last instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (Data.Semigroup.Internal.Alt f) instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (Data.Monoid.Ap f) instance Control.Monad.Fix.MonadFix GHC.Generics.Par1 instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (GHC.Generics.Rec1 f) instance Control.Monad.Fix.MonadFix f => Control.Monad.Fix.MonadFix (GHC.Generics.M1 i c f) instance (Control.Monad.Fix.MonadFix f, Control.Monad.Fix.MonadFix g) => Control.Monad.Fix.MonadFix (f GHC.Generics.:*: g) instance Control.Monad.Fix.MonadFix Data.Ord.Down -- | The identity functor and monad. -- -- This trivial type constructor serves two purposes: -- --
arr id = id
arr (f >>> g) = arr f >>> -- arr g
first (arr f) = arr (first -- f)
first (f >>> g) = first f >>> -- first g
first f >>> arr fst = -- arr fst >>> f
first f >>> arr (id *** g) = -- arr (id *** g) >>> first f
first (first f) >>> arr assoc = -- arr assoc >>> first f
-- assoc ((a,b),c) = (a,(b,c)) ---- -- The other combinators have sensible default definitions, which may be -- overridden for efficiency. class Category a => Arrow a -- | 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 a b Kleisli :: (a -> m b) -> Kleisli m a b [runKleisli] :: Kleisli m a b -> a -> m b -- | The identity arrow, which plays the role of return in arrow -- notation. returnA :: Arrow a => a b b -- | Precomposition with a pure function. (^>>) :: Arrow a => (b -> c) -> a c d -> a b d infixr 1 ^>> -- | Postcomposition with a pure function. (>>^) :: Arrow a => a b c -> (c -> d) -> a b d infixr 1 >>^ -- | Left-to-right composition (>>>) :: Category cat => cat a b -> cat b c -> cat a c infixr 1 >>> -- | Right-to-left composition (<<<) :: Category cat => cat b c -> cat a b -> cat a c infixr 1 <<< -- | Precomposition with a pure function (right-to-left variant). (<<^) :: Arrow a => a c d -> (b -> c) -> a b d infixr 1 <<^ -- | Postcomposition with a pure function (right-to-left variant). (^<<) :: Arrow a => (c -> d) -> a b c -> a b d infixr 1 ^<< class Arrow a => ArrowZero a zeroArrow :: ArrowZero a => a b c -- | A monoid on arrows. class ArrowZero a => ArrowPlus a -- | An associative operation with identity zeroArrow. (<+>) :: ArrowPlus a => a b c -> a b c -> a b c 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: -- --
left (arr f) = arr (left -- f)
left (f >>> g) = left f >>> -- left g
f >>> arr Left = arr -- Left >>> left f
left f >>> arr (id +++ g) = -- arr (id +++ g) >>> left f
left (left f) >>> arr assocsum -- = arr assocsum >>> left f
-- assocsum (Left (Left x)) = Left x -- assocsum (Left (Right y)) = Right (Left y) -- assocsum (Right z) = Right (Right z) ---- -- The other combinators have sensible default definitions, which may be -- overridden for efficiency. class Arrow a => ArrowChoice a -- | 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: -- --
first (arr (\x -> arr (\y -> -- (x,y)))) >>> app = id
first (arr (g >>>)) >>> -- app = second g >>> app
first (arr (>>> h)) >>> -- app = app >>> h
-- assoc ((a,b),c) = (a,(b,c)) -- unassoc (a,(b,c)) = ((a,b),c) --class Arrow a => ArrowLoop a loop :: ArrowLoop a => a (b, d) (c, d) -> a b c instance GHC.Generics.Generic (Control.Arrow.Kleisli m a b) instance GHC.Generics.Generic1 (Control.Arrow.Kleisli m a) instance GHC.Base.Functor m => GHC.Base.Functor (Control.Arrow.Kleisli m a) instance Control.Arrow.ArrowLoop (->) instance Control.Monad.Fix.MonadFix m => Control.Arrow.ArrowLoop (Control.Arrow.Kleisli m) instance Control.Arrow.Arrow a => GHC.Base.Functor (Control.Arrow.ArrowMonad a) instance Control.Arrow.Arrow a => GHC.Base.Applicative (Control.Arrow.ArrowMonad a) instance Control.Arrow.ArrowApply a => GHC.Base.Monad (Control.Arrow.ArrowMonad a) instance Control.Arrow.ArrowPlus a => GHC.Base.Alternative (Control.Arrow.ArrowMonad a) instance (Control.Arrow.ArrowApply a, Control.Arrow.ArrowPlus a) => GHC.Base.MonadPlus (Control.Arrow.ArrowMonad a) instance Control.Arrow.ArrowApply (->) instance GHC.Base.Monad m => Control.Arrow.ArrowApply (Control.Arrow.Kleisli m) instance Control.Arrow.ArrowChoice (->) instance GHC.Base.Monad m => Control.Arrow.ArrowChoice (Control.Arrow.Kleisli m) instance GHC.Base.MonadPlus m => Control.Arrow.ArrowPlus (Control.Arrow.Kleisli m) instance GHC.Base.MonadPlus m => Control.Arrow.ArrowZero (Control.Arrow.Kleisli m) instance GHC.Base.Applicative m => GHC.Base.Applicative (Control.Arrow.Kleisli m a) instance GHC.Base.Alternative m => GHC.Base.Alternative (Control.Arrow.Kleisli m a) instance GHC.Base.Monad m => GHC.Base.Monad (Control.Arrow.Kleisli m a) instance GHC.Base.MonadPlus m => GHC.Base.MonadPlus (Control.Arrow.Kleisli m a) instance GHC.Base.Monad m => Control.Category.Category (Control.Arrow.Kleisli m) instance GHC.Base.Monad m => Control.Arrow.Arrow (Control.Arrow.Kleisli m) instance Control.Arrow.Arrow (->) -- | This module describes a structure intermediate between a functor and a -- monad (technically, a strong lax monoidal functor). Compared with -- monads, this interface lacks the full power of the binding operation -- >>=, but -- --
-- (<*>) = liftA2 id ---- --
-- liftA2 f x y = f <$> x <*> y ---- -- Further, any definition must satisfy the following: -- --
pure id <*> v = -- v
pure (.) <*> u -- <*> v <*> w = u <*> (v -- <*> w)
pure f <*> -- pure x = pure (f x)
u <*> pure y = -- pure ($ y) <*> u
-- forall x y. p (q x y) = f x . g y ---- -- it follows from the above that -- --
-- liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v ---- -- If f is also a Monad, it should satisfy -- -- -- -- (which implies that pure and <*> satisfy the -- applicative functor laws). class Functor f => Applicative f -- | Lift a value. pure :: Applicative f => a -> f a -- | Sequential application. -- -- A few functors support an implementation of <*> that is -- more efficient than the default one. -- -- Using ApplicativeDo: 'fs <*> as' can be -- understood as the do expression -- --
-- do f <- fs -- a <- as -- pure (f a) --(<*>) :: 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. -- -- Using ApplicativeDo: 'liftA2 f as bs' can be -- understood as the do expression -- --
-- do a <- as -- b <- bs -- pure (f a b) --liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c -- | Sequence actions, discarding the value of the first argument. -- -- 'as *> bs' can be understood as the do -- expression -- --
-- do as -- bs ---- -- This is a tad complicated for our ApplicativeDo extension -- which will give it a Monad constraint. For an -- Applicative constraint we write it of the form -- --
-- do _ <- as -- b <- bs -- pure b --(*>) :: Applicative f => f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. -- -- Using ApplicativeDo: 'as <* bs' can be -- understood as the do expression -- --
-- do a <- as -- bs -- pure a --(<*) :: 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 -- | 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 Const :: a -> Const a b [getConst] :: Const a b -> a newtype WrappedMonad m a WrapMonad :: m a -> WrappedMonad m a [unwrapMonad] :: WrappedMonad m a -> m a newtype WrappedArrow a b c WrapArrow :: a b c -> WrappedArrow a b c [unwrapArrow] :: WrappedArrow a b c -> a b c -- | Lists, but with an Applicative functor based on zipping. newtype ZipList a ZipList :: [a] -> ZipList a [getZipList] :: ZipList a -> [a] -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
-- ($) :: (a -> b) -> a -> b -- (<$>) :: Functor f => (a -> b) -> f a -> f b ---- -- Whereas $ is function application, <$> is function -- application lifted over a Functor. -- --
-- >>> 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. -- -- Using ApplicativeDo: 'a <$ bs' can be -- understood as the do expression -- --
-- do bs -- pure a ---- -- with an inferred Functor constraint. (<$) :: Functor f => a -> f b -> f a infixl 4 <$ -- | A variant of <*> with the arguments reversed. -- -- Using ApplicativeDo: 'as <**> fs' can -- be understood as the do expression -- --
-- do a <- as -- f <- fs -- pure (f a) --(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 <**> -- | Lift a function to actions. This function may be used as a value for -- fmap in a Functor instance. -- -- Using ApplicativeDo: 'liftA f as' can be -- understood as the do expression -- --
-- do a <- as -- pure (f a) ---- -- with an inferred Functor constraint, weaker than -- Applicative. liftA :: Applicative f => (a -> b) -> f a -> f b -- | Lift a ternary function to actions. -- -- Using ApplicativeDo: 'liftA3 f as bs cs' can -- be understood as the do expression -- --
-- do a <- as -- b <- bs -- c <- cs -- pure (f a b c) --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. -- --
-- >>> 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) instance GHC.Base.Monad m => GHC.Base.Monad (Control.Applicative.WrappedMonad m) instance GHC.Generics.Generic1 (Control.Applicative.WrappedMonad m) instance GHC.Generics.Generic (Control.Applicative.WrappedMonad m a) instance GHC.Generics.Generic1 (Control.Applicative.WrappedArrow a b) instance GHC.Generics.Generic (Control.Applicative.WrappedArrow a b c) instance GHC.Generics.Generic1 Control.Applicative.ZipList instance GHC.Generics.Generic (Control.Applicative.ZipList a) instance Data.Foldable.Foldable Control.Applicative.ZipList instance GHC.Base.Functor Control.Applicative.ZipList instance GHC.Read.Read a => GHC.Read.Read (Control.Applicative.ZipList a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Control.Applicative.ZipList a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Control.Applicative.ZipList a) instance GHC.Show.Show a => GHC.Show.Show (Control.Applicative.ZipList a) instance GHC.Base.Applicative Control.Applicative.ZipList instance GHC.Base.Alternative Control.Applicative.ZipList instance Control.Arrow.Arrow a => GHC.Base.Functor (Control.Applicative.WrappedArrow a b) instance Control.Arrow.Arrow a => GHC.Base.Applicative (Control.Applicative.WrappedArrow a b) instance (Control.Arrow.ArrowZero a, Control.Arrow.ArrowPlus a) => GHC.Base.Alternative (Control.Applicative.WrappedArrow a b) instance GHC.Base.Monad m => GHC.Base.Functor (Control.Applicative.WrappedMonad m) instance GHC.Base.Monad m => GHC.Base.Applicative (Control.Applicative.WrappedMonad m) instance GHC.Base.MonadPlus m => GHC.Base.Alternative (Control.Applicative.WrappedMonad m) -- | Class of data structures that can be traversed from left to right, -- performing an action on each element. -- -- See also -- --
-- t :: (Applicative f, Applicative g) => f a -> g a ---- -- preserving the Applicative operations, i.e. -- --
-- t (pure x) = pure x -- t (f <*> x) = t f <*> t x ---- -- and the identity functor Identity and composition functors -- Compose are from Data.Functor.Identity and -- Data.Functor.Compose. -- -- A result of the naturality law is a purity law for traverse -- --
-- traverse pure = pure ---- -- (The naturality law is implied by parametricity and thus so is the -- purity law [1, p15].) -- -- Instances are similar to Functor, e.g. given a data type -- --
-- data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) ---- -- a suitable instance would be -- --
-- instance Traversable Tree where -- traverse f Empty = pure Empty -- traverse f (Leaf x) = Leaf <$> f x -- traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r ---- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- --
-- fmapDefault f ≡ runIdentity . traverse (Identity . f) --fmapDefault :: forall t a b. Traversable t => (a -> b) -> t a -> t b -- | This function may be used as a value for foldMap in a -- Foldable instance. -- --
-- foldMapDefault f ≡ getConst . traverse (Const . f) --foldMapDefault :: forall t m a. (Traversable t, Monoid m) => (a -> m) -> t a -> m instance Data.Traversable.Traversable Data.Functor.Identity.Identity instance Data.Traversable.Traversable GHC.Generics.V1 instance Data.Traversable.Traversable GHC.Generics.Par1 instance Data.Traversable.Traversable f => Data.Traversable.Traversable (GHC.Generics.Rec1 f) instance Data.Traversable.Traversable (GHC.Generics.K1 i c) instance Data.Traversable.Traversable f => Data.Traversable.Traversable (GHC.Generics.M1 i c f) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (f GHC.Generics.:+: g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (f GHC.Generics.:*: g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (f GHC.Generics.:.: g) instance Data.Traversable.Traversable GHC.Generics.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 Data.Ord.Down instance Data.Traversable.Traversable GHC.Maybe.Maybe instance Data.Traversable.Traversable [] instance Data.Traversable.Traversable GHC.Base.NonEmpty instance Data.Traversable.Traversable (Data.Either.Either a) instance Data.Traversable.Traversable ((,) a) instance GHC.Ix.Ix i => Data.Traversable.Traversable (GHC.Arr.Array i) instance Data.Traversable.Traversable Data.Proxy.Proxy instance Data.Traversable.Traversable (Data.Functor.Const.Const m) instance Data.Traversable.Traversable Data.Semigroup.Internal.Dual instance Data.Traversable.Traversable Data.Semigroup.Internal.Sum instance Data.Traversable.Traversable Data.Semigroup.Internal.Product instance Data.Traversable.Traversable Data.Monoid.First instance Data.Traversable.Traversable Data.Monoid.Last 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 Data.Traversable.Traversable Control.Applicative.ZipList instance Data.Traversable.Traversable GHC.Generics.U1 -- | Operations on lists. module Data.List -- | Append two lists, i.e., -- --
-- [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] -- [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...] ---- -- If the first list is not finite, the result is the first list. (++) :: [a] -> [a] -> [a] infixr 5 ++ -- | <math>. Extract the first element of a list, which must be -- non-empty. -- --
-- >>> head [1, 2, 3] -- 1 -- -- >>> head [1..] -- 1 -- -- >>> head [] -- Exception: Prelude.head: empty list --head :: [a] -> a -- | <math>. Extract the last element of a list, which must be finite -- and non-empty. -- --
-- >>> last [1, 2, 3] -- 3 -- -- >>> last [1..] -- * Hangs forever * -- -- >>> last [] -- Exception: Prelude.last: empty list --last :: [a] -> a -- | <math>. Extract the elements after the head of a list, which -- must be non-empty. -- --
-- >>> tail [1, 2, 3] -- [2,3] -- -- >>> tail [1] -- [] -- -- >>> tail [] -- Exception: Prelude.tail: empty list --tail :: [a] -> [a] -- | <math>. Return all the elements of a list except the last one. -- The list must be non-empty. -- --
-- >>> init [1, 2, 3] -- [1,2] -- -- >>> init [1] -- [] -- -- >>> init [] -- Exception: Prelude.init: empty list --init :: [a] -> [a] -- | <math>. Decompose a list into its head and tail. -- --
-- >>> uncons [] -- Nothing -- -- >>> uncons [1] -- Just (1,[]) -- -- >>> uncons [1, 2, 3] -- Just (1,[2,3]) --uncons :: [a] -> Maybe (a, [a]) -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. -- --
-- >>> null [] -- True ---- --
-- >>> null [1] -- False ---- -- null terminates even for infinite structures: -- --
-- >>> null [1..] -- False --null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. -- --
-- >>> length [] -- 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, ...] ---- --
-- >>> map (+1) [1, 2, 3] -- [2,3,4] --map :: (a -> b) -> [a] -> [b] -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. -- --
-- >>> 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. -- For example, -- --
-- >>> intersperse ',' "abcde" -- "a,b,c,d,e" --intersperse :: a -> [a] -> [a] -- | intercalate xs xss is equivalent to (concat -- (intersperse xs xss)). It inserts the list xs in -- between the lists in xss and concatenates the result. -- --
-- >>> intercalate ", " ["Lorem", "ipsum", "dolor"] -- "Lorem, ipsum, dolor" --intercalate :: [a] -> [[a]] -> [a] -- | The transpose function transposes the rows and columns of its -- argument. For example, -- --
-- >>> transpose [[1,2,3],[4,5,6]] -- [[1,4],[2,5],[3,6]] ---- -- If some of the rows are shorter than the following rows, their -- elements are skipped: -- --
-- >>> transpose [[10,11],[20],[],[30,31,32]] -- [[10,20,30],[11,31],[32]] --transpose :: [[a]] -> [[a]] -- | The subsequences function returns the list of all subsequences -- of the argument. -- --
-- >>> subsequences "abc" -- ["","a","b","ab","c","ac","bc","abc"] --subsequences :: [a] -> [[a]] -- | The permutations function returns the list of all permutations -- of the argument. -- --
-- >>> permutations "abc" -- ["abc","bac","cba","bca","cab","acb"] --permutations :: [a] -> [[a]] -- | Left-associative fold of a structure. -- -- In the case of lists, foldl, when applied to a binary operator, -- a starting value (typically the left-identity of the operator), and a -- list, reduces the list using the binary operator, from left to right: -- --
-- foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn ---- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldl' -- will diverge if given an infinite list. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is -- that latter does not force the "inner" results (e.g. z `f` x1 -- in the above example) before applying them to the operator (e.g. to -- (`f` x2)). This results in a thunk chain <math> -- elements long, which then must be evaluated from the outside-in. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldl f z = foldl f z . toList ---- --
-- >>> foldl (+) 42 (Node (Leaf 1) 3 (Node Empty 4 (Leaf 2))) -- 52 ---- --
-- >>> foldl (+) 42 Empty -- 42 ---- --
-- >>> foldl (\string nextElement -> nextElement : string) "abcd" (Node (Leaf 'd') 'e' (Node Empty 'f' (Leaf 'g'))) -- "gfedabcd" ---- -- Left-folding infinite structures never terminates: -- --
-- >>> let infiniteNode = Node Empty 1 infiniteNode in foldl (+) 42 infiniteNode -- * Hangs forever * ---- -- Evaluating the head of the result (when applicable) does not -- terminate, unlike foldr: -- --
-- >>> let infiniteNode = Node Empty 'd' infiniteNode in take 5 (foldl (\string nextElement -> nextElement : string) "abc" infiniteNode) -- * Hangs forever * --foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | Left-associative fold of a structure but with strict application of -- the operator. -- -- This ensures that each step of the fold is forced to weak head normal -- form before being applied, avoiding the collection of thunks that -- would otherwise occur. This is often what you want to strictly reduce -- a finite list to a single, monolithic result (e.g. length). -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldl' f z = foldl' f z . toList --foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | A variant of foldl that has no base case, and thus may only be -- applied to non-empty structures. -- -- ⚠️ This function is non-total and will raise a runtime exception if -- the structure happens to be empty. -- --
-- foldl1 f = foldl1 f . toList ---- --
-- >>> 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' :: (a -> a -> a) -> [a] -> a -- | Right-associative fold of a structure. -- -- In the case of lists, foldr, when applied to a binary operator, -- a starting value (typically the right-identity of the operator), and a -- list, reduces the list using the binary operator, from right to left: -- --
-- foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) ---- -- Note that, since the head of the resulting expression is produced by -- an application of the operator to the first element of the list, -- foldr can produce a terminating expression from an infinite -- list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldr f z = foldr f z . toList ---- --
-- >>> foldr (||) False [False, True, False] -- True ---- --
-- >>> foldr (||) False [] -- False ---- --
-- >>> foldr (\nextChar reversedString -> reversedString ++ [nextChar]) "foo" ['a', 'b', 'c', 'd'] -- "foodcba" ---- --
-- >>> foldr (||) False (True : repeat False) -- True ---- -- But the following doesn't terminate: -- --
-- >>> foldr (||) False (repeat False ++ [True]) -- * Hangs forever * ---- --
-- >>> foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (repeat 1) -- [1,4,7,10,13,16,19,22,25,28,31,34,37,40,43... ---- --
-- >>> take 5 $ foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (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. -- --
-- >>> 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. -- --
-- >>> concat (Just [1, 2, 3]) -- [1,2,3] ---- --
-- >>> concat (Node (Leaf [1, 2, 3]) [4, 5] (Node Empty [6] (Leaf []))) -- [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. -- --
-- >>> concatMap (take 3) [[1..], [10..], [100..], [1000..]] -- [1,2,3,10,11,12,100,101,102,1000,1001,1002] ---- --
-- >>> concatMap (take 3) (Node (Leaf [1..]) [10..] Empty) -- [1,2,3,10,11,12] --concatMap :: Foldable t => (a -> [b]) -> t a -> [b] -- | and returns the conjunction of a container of Bools. For the -- result to be True, the container must be finite; False, -- however, results from a False value finitely far from the left -- end. -- --
-- >>> and [] -- 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 :: Foldable t => t Bool -> Bool -- | or returns the disjunction of a container of Bools. For the -- result to be False, the container must be finite; True, -- however, results from a True value finitely far from the left -- end. -- --
-- >>> or [] -- 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 :: Foldable t => t Bool -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> maximum [1..10] -- 10 ---- --
-- >>> maximum [] -- *** Exception: Prelude.maximum: empty list ---- --
-- >>> maximum Nothing -- *** Exception: maximum: empty structure --maximum :: forall a. (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 -- --
-- >>> minimum [1..10] -- 1 ---- --
-- >>> minimum [] -- *** Exception: Prelude.minimum: empty list ---- --
-- >>> minimum Nothing -- *** Exception: minimum: empty structure --minimum :: forall a. (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 ---- --
-- >>> 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"] -- -- >>> scanl (+) 0 [1..] -- * Hangs forever * --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, ...] ---- --
-- >>> 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] -- -- >>> scanl1 (+) [1..] -- * Hangs forever * --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. ---- --
-- >>> 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"] -- -- >>> scanr (+) 0 [1..] -- * Hangs forever * --scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | <math>. scanr1 is a variant of scanr that has no -- starting value argument. -- --
-- >>> 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] -- -- >>> scanr1 (+) [1..] -- * Hangs forever * --scanr1 :: (a -> a -> a) -> [a] -> [a] -- | The mapAccumL function behaves like a combination of -- fmap and foldl; it applies a function to each element of -- a structure, passing an accumulating parameter from left to right, and -- returning a final value of this accumulator together with the new -- structure. mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) -- | The mapAccumR function behaves like a combination of -- fmap and foldr; it applies a function to each element of -- a structure, passing an accumulating parameter from right to left, and -- returning a final value of this accumulator together with the new -- structure. mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) -- | iterate f x returns an infinite list of repeated -- applications of f to x: -- --
-- iterate f x == [x, f x, f (f x), ...] ---- -- 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. -- --
-- >>> iterate not True -- [True,False,True,False... -- -- >>> iterate (+3) 42 -- [42,45,48,51,54,57,60,63... --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. iterate' :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. -- --
-- >>> repeat 17 -- [17,17,17,17,17,17,17,17,17... --repeat :: a -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. -- --
-- >>> replicate 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. -- --
-- >>> cycle [] -- Exception: Prelude.cycle: empty list -- -- >>> cycle [42] -- [42,42,42,42,42,42,42,42,42,42... -- -- >>> cycle [2, 5, 7] -- [2,5,7,2,5,7,2,5,7,2,5,7... --cycle :: [a] -> [a] -- | The unfoldr function is a `dual' to foldr: while -- foldr reduces a list to a summary value, unfoldr builds -- a list from a seed value. The function takes the element and returns -- Nothing if it is done producing the list or returns Just -- (a,b), in which case, a is a prepended to the list -- and b is used as the next element in a recursive call. For -- example, -- --
-- iterate f == unfoldr (\x -> Just (x, f x)) ---- -- In some cases, unfoldr can undo a foldr operation: -- --
-- unfoldr f' (foldr f z xs) == xs ---- -- if the following holds: -- --
-- f' (f x y) = Just (x,y) -- f' z = Nothing ---- -- A simple use of unfoldr: -- --
-- >>> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10 -- [10,9,8,7,6,5,4,3,2,1] --unfoldr :: (b -> Maybe (a, b)) -> b -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n > length xs. -- --
-- >>> take 5 "Hello World!" -- "Hello" -- -- >>> take 3 [1,2,3,4,5] -- [1,2,3] -- -- >>> take 3 [1,2] -- [1,2] -- -- >>> take 3 [] -- [] -- -- >>> take (-1) [1,2] -- [] -- -- >>> take 0 [1,2] -- [] ---- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. take :: Int -> [a] -> [a] -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n > length -- xs. -- --
-- >>> drop 6 "Hello World!" -- "World!" -- -- >>> drop 3 [1,2,3,4,5] -- [4,5] -- -- >>> drop 3 [1,2] -- [] -- -- >>> drop 3 [] -- [] -- -- >>> drop (-1) [1,2] -- [1,2] -- -- >>> drop 0 [1,2] -- [1,2] ---- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. drop :: Int -> [a] -> [a] -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
-- >>> splitAt 6 "Hello World!" -- ("Hello ","World!") -- -- >>> splitAt 3 [1,2,3,4,5] -- ([1,2,3],[4,5]) -- -- >>> splitAt 1 [1,2,3] -- ([1],[2,3]) -- -- >>> splitAt 3 [1,2,3] -- ([1,2,3],[]) -- -- >>> splitAt 4 [1,2,3] -- ([1,2,3],[]) -- -- >>> splitAt 0 [1,2,3] -- ([],[1,2,3]) -- -- >>> splitAt (-1) [1,2,3] -- ([],[1,2,3]) ---- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) -- | takeWhile, applied to a predicate p and a list -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p. -- --
-- >>> takeWhile (< 3) [1,2,3,4,1,2,3,4] -- [1,2] -- -- >>> takeWhile (< 9) [1,2,3] -- [1,2,3] -- -- >>> takeWhile (< 0) [1,2,3] -- [] --takeWhile :: (a -> Bool) -> [a] -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. -- --
-- >>> dropWhile (< 3) [1,2,3,4,5,1,2,3] -- [3,4,5,1,2,3] -- -- >>> dropWhile (< 9) [1,2,3] -- [] -- -- >>> dropWhile (< 0) [1,2,3] -- [1,2,3] --dropWhile :: (a -> Bool) -> [a] -> [a] -- | The dropWhileEnd function drops the largest suffix of a list in -- which the given predicate holds for all elements. For example: -- --
-- >>> dropWhileEnd isSpace "foo\n" -- "foo" ---- --
-- >>> dropWhileEnd isSpace "foo bar" -- "foo bar" ---- --
-- dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined --dropWhileEnd :: (a -> Bool) -> [a] -> [a] -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is longest prefix (possibly empty) -- of xs of elements that satisfy p and second element -- is the remainder of the list: -- --
-- >>> span (< 3) [1,2,3,4,1,2,3,4] -- ([1,2],[3,4,1,2,3,4]) -- -- >>> span (< 9) [1,2,3] -- ([1,2,3],[]) -- -- >>> span (< 0) [1,2,3] -- ([],[1,2,3]) ---- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | break, applied to a predicate p and a list -- xs, returns a tuple where first element is longest prefix -- (possibly empty) of xs of elements that do not satisfy -- p and second element is the remainder of the list: -- --
-- >>> break (> 3) [1,2,3,4,1,2,3,4] -- ([1,2,3],[4,1,2,3,4]) -- -- >>> break (< 9) [1,2,3] -- ([],[1,2,3]) -- -- >>> break (> 9) [1,2,3] -- ([1,2,3],[]) ---- -- break p is equivalent to span (not . -- p). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | <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. -- --
-- >>> stripPrefix "foo" "foobar" -- Just "bar" ---- --
-- >>> stripPrefix "foo" "foo" -- Just "" ---- --
-- >>> stripPrefix "foo" "barfoo" -- Nothing ---- --
-- >>> stripPrefix "foo" "barfoobaz" -- Nothing --stripPrefix :: Eq a => [a] -> [a] -> Maybe [a] -- | The group function takes a list and returns a list of lists -- such that the concatenation of the result is equal to the argument. -- Moreover, each sublist in the result contains only equal elements. For -- example, -- --
-- >>> group "Mississippi" -- ["M","i","ss","i","ss","i","pp","i"] ---- -- It is a special case of groupBy, which allows the programmer to -- supply their own equality test. group :: Eq a => [a] -> [[a]] -- | The inits function returns all initial segments of the -- argument, shortest first. For example, -- --
-- >>> inits "abc" -- ["","a","ab","abc"] ---- -- Note that inits has the following strictness property: -- inits (xs ++ _|_) = inits xs ++ _|_ -- -- In particular, inits _|_ = [] : _|_ inits :: [a] -> [[a]] -- | <math>. The tails function returns all final segments of -- the argument, longest first. For example, -- --
-- >>> tails "abc" -- ["abc","bc","c",""] ---- -- Note that tails has the following strictness property: -- tails _|_ = _|_ : _|_ tails :: [a] -> [[a]] -- | <math>. The isPrefixOf function takes two lists and -- returns True iff the first list is a prefix of the second. -- --
-- >>> "Hello" `isPrefixOf` "Hello World!" -- True ---- --
-- >>> "Hello" `isPrefixOf` "Wello Horld!" -- False --isPrefixOf :: Eq a => [a] -> [a] -> Bool -- | The isSuffixOf function takes two lists and returns True -- iff the first list is a suffix of the second. The second list must be -- finite. -- --
-- >>> "ld!" `isSuffixOf` "Hello World!" -- True ---- --
-- >>> "World" `isSuffixOf` "Hello World!" -- False --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. -- --
-- >>> isInfixOf "Haskell" "I really like Haskell." -- True ---- --
-- >>> isInfixOf "Ial" "I really like Haskell." -- False --isInfixOf :: Eq a => [a] -> [a] -> Bool -- | The isSubsequenceOf function takes two lists and returns -- True if all the elements of the first list occur, in order, in -- the second. The elements do not have to occur consecutively. -- -- isSubsequenceOf x y is equivalent to elem x -- (subsequences y). -- --
-- >>> isSubsequenceOf "GHC" "The Glorious Haskell Compiler" -- True -- -- >>> isSubsequenceOf ['a','d'..'z'] ['a'..'z'] -- True -- -- >>> isSubsequenceOf [1..10] [10,9..0] -- False --isSubsequenceOf :: Eq a => [a] -> [a] -> Bool -- | Does the element occur in the structure? -- -- Note: elem is often used in infix form. -- --
-- >>> 3 `elem` [] -- False ---- --
-- >>> 3 `elem` [1,2] -- False ---- --
-- >>> 3 `elem` [1,2,3,4,5] -- True ---- -- For infinite structures, elem terminates if the 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> find (> 42) [0, 5..] -- Just 45 ---- --
-- >>> find (> 4) (Node (Leaf 3) 17 (Node Empty 12 (Leaf 8))) -- Just 17 ---- --
-- >>> 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] ---- --
-- >>> filter odd [1, 2, 3] -- [1,3] --filter :: (a -> Bool) -> [a] -> [a] -- | The partition function takes a predicate a list and returns the -- pair of lists of elements which do and do not satisfy the predicate, -- respectively; i.e., -- --
-- partition p xs == (filter p xs, filter (not . p) xs) ---- --
-- >>> partition (`elem` "aeiou") "Hello World!" -- ("eoo","Hll Wrld!") --partition :: (a -> Bool) -> [a] -> ([a], [a]) -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. -- --
-- >>> ['a', '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 --(!!) :: [a] -> Int -> a infixl 9 !! -- | The elemIndex function returns the index of the first element -- in the given list which is equal (by ==) to the query element, -- or Nothing if there is no such element. -- --
-- >>> elemIndex 4 [0..] -- Just 4 --elemIndex :: Eq a => a -> [a] -> Maybe Int -- | The elemIndices function extends elemIndex, by returning -- the indices of all elements equal to the query element, in ascending -- order. -- --
-- >>> elemIndices 'o' "Hello World" -- [4,7] --elemIndices :: Eq a => a -> [a] -> [Int] -- | The findIndex function takes a predicate and a list and returns -- the index of the first element in the list satisfying the predicate, -- or Nothing if there is no such element. -- --
-- >>> findIndex isSpace "Hello World!" -- Just 5 --findIndex :: (a -> Bool) -> [a] -> Maybe Int -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. -- --
-- >>> findIndices (`elem` "aeiou") "Hello World!" -- [1,4,7] --findIndices :: (a -> Bool) -> [a] -> [Int] -- | <math>. zip takes two lists and returns a list of -- corresponding pairs. -- --
-- >>> zip [1, 2] ['a', 'b'] -- [(1, 'a'), (2, 'b')] ---- -- 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 is right-lazy: -- --
-- >>> zip [] _|_ -- [] -- -- >>> zip _|_ [] -- _|_ ---- -- zip is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. 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..] ---- -- For example, zipWith (+) is applied to two lists to -- produce the list of corresponding sums: -- --
-- >>> zipWith (+) [1, 2, 3] [4, 5, 6] -- [5,7,9] ---- -- zipWith is right-lazy: -- --
-- >>> zipWith f [] _|_ -- [] ---- -- zipWith is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | The zipWith3 function takes a function which combines three -- elements, as well as three lists and returns a list of 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..] --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. -- --
-- >>> 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, analogous to unzip. -- --
-- >>> 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]) -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
-- >>> lines "" -- [] ---- --
-- >>> lines "\n" -- [""] ---- --
-- >>> lines "one" -- ["one"] ---- --
-- >>> lines "one\n" -- ["one"] ---- --
-- >>> lines "one\n\n" -- ["one",""] ---- --
-- >>> lines "one\ntwo" -- ["one","two"] ---- --
-- >>> lines "one\ntwo\n" -- ["one","two"] ---- -- Thus lines s contains at least as many elements as -- newlines in s. lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space. -- --
-- >>> words "Lorem ipsum\ndolor" -- ["Lorem","ipsum","dolor"] --words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. -- --
-- >>> unlines ["Hello", "World", "!"] -- "Hello\nWorld\n!\n" --unlines :: [String] -> String -- | unwords is an inverse operation to words. It joins words -- with separating spaces. -- --
-- >>> unwords ["Lorem", "ipsum", "dolor"] -- "Lorem ipsum dolor" --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. -- --
-- >>> nub [1,2,3,4,3,2,1,2,4,3,5] -- [1,2,3,4,5] --nub :: Eq a => [a] -> [a] -- | <math>. delete x removes the first occurrence of -- x from its list argument. For example, -- --
-- >>> delete 'a' "banana" -- "bnana" ---- -- It is a special case of deleteBy, which allows the programmer -- to supply their own equality test. delete :: Eq a => a -> [a] -> [a] -- | The \\ function is list difference (non-associative). In the -- result of xs \\ ys, the first occurrence of -- each element of ys in turn (if any) has been removed from -- xs. Thus -- --
-- (xs ++ ys) \\ xs == ys. ---- --
-- >>> "Hello World!" \\ "ell W" -- "Hoorld!" ---- -- It is a special case of deleteFirstsBy, which allows the -- programmer to supply their own equality test. (\\) :: Eq a => [a] -> [a] -> [a] infix 5 \\ -- | The union function returns the list union of the two lists. For -- example, -- --
-- >>> "dog" `union` "cow" -- "dogcw" ---- -- Duplicates, and elements of the first list, are removed from the the -- second list, but if the first list contains duplicates, so will the -- result. It is a special case of unionBy, which allows the -- programmer to supply their own equality test. union :: Eq a => [a] -> [a] -> [a] -- | The intersect function takes the list intersection of two -- lists. For example, -- --
-- >>> [1,2,3,4] `intersect` [2,4,6,8] -- [2,4] ---- -- If the first list contains duplicates, so will the result. -- --
-- >>> [1,2,2,3,4] `intersect` [6,4,4,2] -- [2,2,4] ---- -- It is a special case of intersectBy, which allows the -- programmer to supply their own equality test. If the element is found -- in both the first and the second list, the element from the first list -- will be used. intersect :: Eq a => [a] -> [a] -> [a] -- | The sort function implements a stable sorting algorithm. It is -- a special case of sortBy, which allows the programmer to supply -- their own comparison function. -- -- Elements are arranged from lowest to highest, keeping duplicates in -- the order they appeared in the input. -- --
-- >>> sort [1,6,4,3,2,5] -- [1,2,3,4,5,6] --sort :: Ord a => [a] -> [a] -- | Sort a list by comparing the results of a key function applied to each -- element. sortOn f is equivalent to sortBy (comparing -- f), but has the performance advantage of only evaluating -- f once for each element in the input list. This is called the -- decorate-sort-undecorate paradigm, or Schwartzian transform. -- -- Elements are arranged from from lowest to highest, keeping duplicates -- in the order they appeared in the input. -- --
-- >>> sortOn fst [(2, "world"), (4, "!"), (1, "Hello")] -- [(1,"Hello"),(2,"world"),(4,"!")] --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. -- --
-- >>> 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. -- --
-- >>> nubBy (\x y -> mod x 3 == mod y 3) [1,2,4,5,6] -- [1,2,6] --nubBy :: (a -> a -> Bool) -> [a] -> [a] -- | <math>. The deleteBy function behaves like delete, -- but takes a user-supplied equality predicate. -- --
-- >>> deleteBy (<=) 4 [1..10] -- [1,2,3,5,6,7,8,9,10] --deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a] -- | The deleteFirstsBy function takes a predicate and two lists and -- returns the first list with the first occurrence of each element of -- the second list removed. deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The unionBy function is the non-overloaded version of -- union. unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The intersectBy function is the non-overloaded version of -- intersect. intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (a -> a -> Bool) -> [a] -> [[a]] -- | The sortBy function is the non-overloaded version of -- sort. -- --
-- >>> sortBy (\(a,_) (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. insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] -- | The largest element of a non-empty structure with respect to the given -- comparison function. -- --
-- >>> maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"] -- "Longest" --maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | The least element of a non-empty structure with respect to the given -- comparison function. -- --
-- >>> minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"] -- "!" --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. -- --
-- >>> genericLength [1, 2, 3] :: Int -- 3 -- -- >>> genericLength [1, 2, 3] :: Float -- 3.0 --genericLength :: Num i => [a] -> i -- | The genericTake function is an overloaded version of -- take, which accepts any Integral value as the number of -- elements to take. genericTake :: Integral i => i -> [a] -> [a] -- | The genericDrop function is an overloaded version of -- drop, which accepts any Integral value as the number of -- elements to drop. genericDrop :: Integral i => i -> [a] -> [a] -- | The genericSplitAt function is an overloaded version of -- splitAt, which accepts any Integral value as the -- position at which to split. genericSplitAt :: Integral i => i -> [a] -> ([a], [a]) -- | The genericIndex function is an overloaded version of -- !!, which accepts any Integral value as the index. genericIndex :: Integral i => [a] -> i -> a -- | The genericReplicate function is an overloaded version of -- replicate, which accepts any Integral value as the -- number of repetitions to make. genericReplicate :: Integral i => i -> a -> [a] -- | Functions for tracing and monitoring execution. -- -- These can be useful for investigating bugs or performance problems. -- They should not be used in production code. module Debug.Trace -- | The trace function outputs the trace message given as its first -- argument, before returning the second argument as its result. -- -- For example, this returns the value of f x but first outputs -- the message. -- --
-- >>> 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 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 -- | The traceEventIO function emits a message to the eventlog, if -- eventlog profiling is available and enabled at runtime. -- -- Compared to traceEvent, traceEventIO sequences the event -- with respect to other IO actions. traceEventIO :: String -> IO () -- | The traceMarker function emits a marker to the eventlog, if -- eventlog profiling is available and enabled at runtime. The -- String is the name of the marker. The name is just used in -- the profiling tools to help you keep clear which marker is which. -- -- This function is suitable for use in pure code. In an IO context use -- traceMarkerIO instead. -- -- Note that when using GHC's SMP runtime, it is possible (but rare) to -- get duplicate events emitted if two CPUs simultaneously evaluate the -- same thunk that uses traceMarker. traceMarker :: String -> a -> a -- | The traceMarkerIO function emits a marker to the eventlog, if -- eventlog profiling is available and enabled at runtime. -- -- Compared to traceMarker, traceMarkerIO sequences the -- event with respect to other IO actions. traceMarkerIO :: String -> IO () -- | The String type and associated operations. module Data.String -- | A String is a list of characters. String constants in Haskell -- are values of type String. -- -- See Data.List for operations on lists. type String = [Char] -- | Class for string-like datastructures; used by the overloaded string -- extension (-XOverloadedStrings in GHC). class IsString a fromString :: IsString a => String -> a -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
-- >>> lines "" -- [] ---- --
-- >>> lines "\n" -- [""] ---- --
-- >>> lines "one" -- ["one"] ---- --
-- >>> lines "one\n" -- ["one"] ---- --
-- >>> lines "one\n\n" -- ["one",""] ---- --
-- >>> lines "one\ntwo" -- ["one","two"] ---- --
-- >>> lines "one\ntwo\n" -- ["one","two"] ---- -- Thus lines s contains at least as many elements as -- newlines in s. lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space. -- --
-- >>> words "Lorem ipsum\ndolor" -- ["Lorem","ipsum","dolor"] --words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. -- --
-- >>> unlines ["Hello", "World", "!"] -- "Hello\nWorld\n!\n" --unlines :: [String] -> String -- | unwords is an inverse operation to words. It joins words -- with separating spaces. -- --
-- >>> unwords ["Lorem", "ipsum", "dolor"] -- "Lorem ipsum dolor" --unwords :: [String] -> String instance Data.String.IsString a => Data.String.IsString (Data.Functor.Const.Const a b) instance Data.String.IsString a => Data.String.IsString (Data.Functor.Identity.Identity a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString [a] -- | A general library for representation and manipulation of versions. -- -- Versioning schemes are many and varied, so the version representation -- provided by this library is intended to be a compromise between -- complete generality, where almost no common functionality could -- reasonably be provided, and fixing a particular versioning scheme, -- which would probably be too restrictive. -- -- So the approach taken here is to provide a representation which -- subsumes many of the versioning schemes commonly in use, and we -- provide implementations of Eq, Ord and conversion -- to/from String which will be appropriate for some applications, -- but not all. module Data.Version -- | A Version represents the version of a software entity. -- -- An instance of Eq is provided, which implements exact equality -- modulo reordering of the tags in the versionTags field. -- -- An instance of Ord is also provided, which gives lexicographic -- ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 -- > 1.2.2, etc.). This is expected to be sufficient for many uses, -- but note that you may need to use a more specific ordering for your -- versioning scheme. For example, some versioning schemes may include -- pre-releases which have tags "pre1", "pre2", and so -- on, and these would need to be taken into account when determining -- ordering. In some cases, date ordering may be more appropriate, so the -- application would have to look for date tags in the -- versionTags field and compare those. The bottom line is, don't -- always assume that compare and other Ord operations are -- the right thing for every Version. -- -- Similarly, concrete representations of versions may differ. One -- possible concrete representation is provided (see showVersion -- and parseVersion), but depending on the application a different -- concrete representation may be more appropriate. data Version Version :: [Int] -> [String] -> Version -- | The numeric branch for this version. This reflects the fact that most -- software versions are tree-structured; there is a main trunk which is -- tagged with versions at various points (1,2,3...), and the first -- branch off the trunk after version 3 is 3.1, the second branch off the -- trunk after version 3 is 3.2, and so on. The tree can be branched -- arbitrarily, just by adding more digits. -- -- We represent the branch as a list of Int, so version 3.2.1 -- becomes [3,2,1]. Lexicographic ordering (i.e. the default instance of -- Ord for [Int]) gives the natural ordering of branches. [versionBranch] :: Version -> [Int] -- | A version can be tagged with an arbitrary list of strings. The -- interpretation of the list of tags is entirely dependent on the entity -- that this version applies to. -- | Deprecated: See GHC ticket #2496 [versionTags] :: Version -> [String] -- | Provides one possible concrete representation for Version. For -- a version with versionBranch = [1,2,3] and -- versionTags = ["tag1","tag2"], the output will be -- 1.2.3-tag1-tag2. showVersion :: Version -> String -- | A parser for versions in the format produced by showVersion. parseVersion :: ReadP Version -- | Construct tag-less Version makeVersion :: [Int] -> Version instance GHC.Generics.Generic Data.Version.Version instance GHC.Show.Show Data.Version.Version instance GHC.Read.Read Data.Version.Version instance GHC.Classes.Eq Data.Version.Version instance GHC.Classes.Ord Data.Version.Version -- | GHC Extensions: this is the Approved Way to get at GHC-specific -- extensions. -- -- Note: no other base module should import this module. module GHC.Exts -- | A fixed-precision integer type with at least the range [-2^29 .. -- 2^29-1]. The exact range for a given implementation can be -- determined by using minBound and maxBound from the -- Bounded class. data Int I# :: Int# -> Int -- | A Word is an unsigned integral type, with the same size as -- Int. data Word W# :: Word# -> Word -- | Single-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- single-precision type. data Float F# :: Float# -> Float -- | Double-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- double-precision type. data Double D# :: Double# -> Double -- | The character type Char is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. -- characters, see http://www.unicode.org/ for details). This set -- extends the ISO 8859-1 (Latin-1) character set (the first 256 -- characters), which is itself an extension of the ASCII character set -- (the first 128 characters). A character literal in Haskell has type -- Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char C# :: Char# -> Char -- | A value of type Ptr a represents a pointer to an -- object, or an array of objects, which may be marshalled to or from -- Haskell values of type a. -- -- The type a will often be an instance of class Storable -- which provides the marshalling operations. However this is not -- essential, and you can provide your own operations to access the -- pointer. For example you might write small foreign functions to get or -- set the fields of a C struct. data Ptr a Ptr :: Addr# -> Ptr a -- | A value of type FunPtr a is a pointer to a function -- callable from foreign code. The type a will normally be a -- foreign type, a function type with zero or more arguments where -- --
-- foreign import ccall "stdlib.h &free" -- p_free :: FunPtr (Ptr a -> IO ()) ---- -- or a pointer to a Haskell function created using a wrapper stub -- declared to produce a FunPtr of the correct type. For example: -- --
-- type Compare = Int -> Int -> Bool -- foreign import ccall "wrapper" -- mkCompare :: Compare -> IO (FunPtr Compare) ---- -- Calls to wrapper stubs like mkCompare allocate storage, which -- should be released with freeHaskellFunPtr when no longer -- required. -- -- To convert FunPtr values to corresponding Haskell functions, -- one can define a dynamic stub for the specific foreign type, -- e.g. -- --
-- type IntFunction = CInt -> IO () -- foreign import ccall "dynamic" -- mkFun :: FunPtr IntFunction -> IntFunction --data FunPtr a FunPtr :: Addr# -> FunPtr a maxTupleSize :: Int -- | 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` realWorld# :: State# RealWorld void# :: Void# -- | The null address. nullAddr# :: Addr# magicDict :: a -- | Witness for an unboxed Proxy# value, which has no runtime -- representation. proxy# :: forall {k} (a :: k). Proxy# a -- | An arbitrary machine address assumed to point outside the -- garbage-collected heap. data Addr# :: TYPE 'AddrRep data Array# a :: TYPE 'UnliftedRep data ByteArray# :: TYPE 'UnliftedRep data Char# :: TYPE 'WordRep data Double# :: TYPE 'DoubleRep data Float# :: TYPE 'FloatRep data Int# :: TYPE 'IntRep data Int8# :: TYPE 'Int8Rep data Int16# :: TYPE 'Int16Rep data Int32# :: TYPE 'Int32Rep data Int64# :: TYPE 'Int64Rep data Weak# a :: TYPE 'UnliftedRep data MutableArray# a b :: TYPE 'UnliftedRep data MutableByteArray# a :: TYPE 'UnliftedRep -- | 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 'UnliftedRep -- | 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 'AddrRep data ArrayArray# :: TYPE 'UnliftedRep data MutableArrayArray# a :: TYPE 'UnliftedRep -- | 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 :: TYPE 'TupleRep '[] :: [RuntimeRep] data StableName# a :: TYPE 'UnliftedRep -- | A MutVar# behaves like a single-element mutable array. data MutVar# a b :: TYPE 'UnliftedRep data Void# :: TYPE 'TupleRep '[] :: [RuntimeRep] data Word# :: TYPE 'WordRep data Word8# :: TYPE 'Word8Rep data Word16# :: TYPE 'Word16Rep data Word32# :: TYPE 'Word32Rep data Word64# :: TYPE 'Word64Rep -- | (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# :: TYPE 'UnliftedRep -- | Primitive bytecode type. data BCO data TVar# a b :: TYPE 'UnliftedRep data Compact# :: TYPE 'UnliftedRep -- | 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) :: TYPE 'TupleRep '[] :: [RuntimeRep] data SmallArray# a :: TYPE 'UnliftedRep data SmallMutableArray# a b :: TYPE 'UnliftedRep -- | 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 gtChar# :: Char# -> Char# -> Int# geChar# :: Char# -> Char# -> Int# eqChar# :: Char# -> Char# -> Int# neChar# :: Char# -> Char# -> Int# ltChar# :: Char# -> Char# -> Int# leChar# :: Char# -> Char# -> Int# ord# :: Char# -> Int# extendInt8# :: Int8# -> Int# narrowInt8# :: Int# -> Int8# negateInt8# :: Int8# -> Int8# plusInt8# :: Int8# -> Int8# -> Int8# subInt8# :: Int8# -> Int8# -> Int8# timesInt8# :: Int8# -> Int8# -> Int8# -- | Warning: this can fail with an unchecked exception. quotInt8# :: Int8# -> Int8# -> Int8# -- | Warning: this can fail with an unchecked exception. remInt8# :: Int8# -> Int8# -> Int8# -- | Warning: this can fail with an unchecked exception. quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #) eqInt8# :: Int8# -> Int8# -> Int# geInt8# :: Int8# -> Int8# -> Int# gtInt8# :: Int8# -> Int8# -> Int# leInt8# :: Int8# -> Int8# -> Int# ltInt8# :: Int8# -> Int8# -> Int# neInt8# :: Int8# -> Int8# -> Int# extendWord8# :: Word8# -> Word# narrowWord8# :: Word# -> Word8# notWord8# :: Word8# -> Word8# plusWord8# :: Word8# -> Word8# -> Word8# subWord8# :: Word8# -> Word8# -> Word8# timesWord8# :: Word8# -> Word8# -> Word8# -- | Warning: this can fail with an unchecked exception. quotWord8# :: Word8# -> Word8# -> Word8# -- | Warning: this can fail with an unchecked exception. remWord8# :: Word8# -> Word8# -> Word8# -- | Warning: this can fail with an unchecked exception. quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #) eqWord8# :: Word8# -> Word8# -> Int# geWord8# :: Word8# -> Word8# -> Int# gtWord8# :: Word8# -> Word8# -> Int# leWord8# :: Word8# -> Word8# -> Int# ltWord8# :: Word8# -> Word8# -> Int# neWord8# :: Word8# -> Word8# -> Int# extendInt16# :: Int16# -> Int# narrowInt16# :: Int# -> Int16# negateInt16# :: Int16# -> Int16# plusInt16# :: Int16# -> Int16# -> Int16# subInt16# :: Int16# -> Int16# -> Int16# timesInt16# :: Int16# -> Int16# -> Int16# -- | Warning: this can fail with an unchecked exception. quotInt16# :: Int16# -> Int16# -> Int16# -- | Warning: this can fail with an unchecked exception. remInt16# :: Int16# -> Int16# -> Int16# -- | Warning: this can fail with an unchecked exception. quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #) eqInt16# :: Int16# -> Int16# -> Int# geInt16# :: Int16# -> Int16# -> Int# gtInt16# :: Int16# -> Int16# -> Int# leInt16# :: Int16# -> Int16# -> Int# ltInt16# :: Int16# -> Int16# -> Int# neInt16# :: Int16# -> Int16# -> Int# extendWord16# :: Word16# -> Word# narrowWord16# :: Word# -> Word16# notWord16# :: Word16# -> Word16# plusWord16# :: Word16# -> Word16# -> Word16# subWord16# :: Word16# -> Word16# -> Word16# timesWord16# :: Word16# -> Word16# -> Word16# -- | Warning: this can fail with an unchecked exception. quotWord16# :: Word16# -> Word16# -> Word16# -- | Warning: this can fail with an unchecked exception. remWord16# :: Word16# -> Word16# -> Word16# -- | Warning: this can fail with an unchecked exception. quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #) eqWord16# :: Word16# -> Word16# -> Int# geWord16# :: Word16# -> Word16# -> Int# gtWord16# :: Word16# -> Word16# -> Int# leWord16# :: Word16# -> Word16# -> Int# ltWord16# :: Word16# -> Word16# -> Int# neWord16# :: Word16# -> Word16# -> Int# (+#) :: Int# -> Int# -> Int# infixl 6 +# (-#) :: Int# -> Int# -> Int# infixl 6 -# -- | Low word of signed integer multiply. (*#) :: Int# -> Int# -> Int# infixl 7 *# -- | 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). timesInt2# :: Int# -> Int# -> (# 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# -- | 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# -- | 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. -- -- Warning: this can fail with an unchecked exception. quotRemInt# :: Int# -> Int# -> (# Int#, Int# #) -- | Bitwise "and". andI# :: Int# -> Int# -> Int# -- | Bitwise "or". orI# :: Int# -> Int# -> Int# -- | Bitwise "xor". xorI# :: Int# -> Int# -> Int# -- | Bitwise "not", also known as the binary complement. notI# :: 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# -- | 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# #) -- | 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# #) (>#) :: 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 <=# chr# :: Int# -> Char# int2Word# :: Int# -> Word# int2Float# :: Int# -> Float# int2Double# :: Int# -> Double# word2Float# :: Word# -> Float# word2Double# :: Word# -> Double# -- | Shift left. Result undefined if shift amount is not in the range 0 to -- word size - 1 inclusive. uncheckedIShiftL# :: 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 right logical. Result undefined if shift amount is not in the -- range 0 to word size - 1 inclusive. uncheckedIShiftRL# :: Int# -> Int# -> Int# plusWord# :: Word# -> Word# -> Word# -- | 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# #) -- | 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, 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# #) minusWord# :: Word# -> Word# -> Word# timesWord# :: Word# -> Word# -> Word# timesWord2# :: Word# -> Word# -> (# Word#, Word# #) -- | Warning: this can fail with an unchecked exception. quotWord# :: Word# -> Word# -> Word# -- | Warning: this can fail with an unchecked exception. remWord# :: Word# -> Word# -> Word# -- | Warning: this can fail with an unchecked exception. quotRemWord# :: Word# -> 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# #) and# :: Word# -> Word# -> Word# or# :: Word# -> Word# -> Word# xor# :: Word# -> Word# -> Word# not# :: Word# -> Word# -- | Shift left logical. Result undefined if shift amount is not in the -- range 0 to word size - 1 inclusive. uncheckedShiftL# :: Word# -> Int# -> Word# -- | Shift right logical. Result undefined if shift amount is not in the -- range 0 to word size - 1 inclusive. uncheckedShiftRL# :: Word# -> Int# -> Word# word2Int# :: Word# -> Int# gtWord# :: Word# -> Word# -> Int# geWord# :: Word# -> Word# -> Int# eqWord# :: Word# -> Word# -> Int# neWord# :: Word# -> Word# -> Int# ltWord# :: Word# -> Word# -> Int# leWord# :: Word# -> Word# -> Int# -- | Count the number of set bits in the lower 8 bits of a word. popCnt8# :: 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 32 bits of a word. popCnt32# :: Word# -> Word# -- | Count the number of set bits in a 64-bit word. popCnt64# :: Word# -> Word# -- | Count the number of set bits in a word. popCnt# :: Word# -> Word# -- | Deposit bits to lower 8 bits of a word at locations specified by a -- mask. pdep8# :: 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 32 bits of a word at locations specified by a -- mask. pdep32# :: Word# -> Word# -> Word# -- | Deposit bits to a word at locations specified by a mask. pdep64# :: Word# -> Word# -> Word# -- | Deposit bits to a word at locations specified by a mask. pdep# :: Word# -> Word# -> Word# -- | Extract bits from lower 8 bits of a word at locations specified by a -- mask. pext8# :: 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 32 bits of a word at locations specified by a -- mask. pext32# :: Word# -> Word# -> Word# -- | Extract bits from a word at locations specified by a mask. pext64# :: Word# -> Word# -> Word# -- | Extract bits from a word at locations specified by a mask. pext# :: Word# -> Word# -> Word# -- | Count leading zeros in the lower 8 bits of a word. clz8# :: Word# -> Word# -- | Count leading zeros in the lower 16 bits of a word. clz16# :: Word# -> Word# -- | Count leading zeros in the lower 32 bits of a word. clz32# :: Word# -> Word# -- | Count leading zeros in a 64-bit word. clz64# :: Word# -> Word# -- | Count leading zeros in a word. clz# :: Word# -> Word# -- | Count trailing zeros in the lower 8 bits of a word. ctz8# :: Word# -> Word# -- | Count trailing zeros in the lower 16 bits of a word. ctz16# :: Word# -> Word# -- | Count trailing zeros in the lower 32 bits of a word. ctz32# :: Word# -> Word# -- | Count trailing zeros in a 64-bit word. ctz64# :: Word# -> Word# -- | Count trailing zeros in a word. ctz# :: Word# -> Word# -- | Swap bytes in the lower 16 bits of a word. The higher bytes are -- undefined. byteSwap16# :: Word# -> Word# -- | Swap bytes in the lower 32 bits of a word. The higher bytes are -- undefined. byteSwap32# :: Word# -> Word# -- | Swap bytes in a 64 bits of a word. byteSwap64# :: Word# -> Word# -- | Swap bytes in a word. byteSwap# :: Word# -> Word# -- | Reverse the order of the bits in a 8-bit word. bitReverse8# :: Word# -> Word# -- | Reverse the order of the bits in a 16-bit word. bitReverse16# :: Word# -> Word# -- | Reverse the order of the bits in a 32-bit word. bitReverse32# :: Word# -> Word# -- | Reverse the order of the bits in a 64-bit word. bitReverse64# :: Word# -> Word# -- | Reverse the order of the bits in a word. bitReverse# :: Word# -> Word# narrow8Int# :: Int# -> Int# narrow16Int# :: Int# -> Int# narrow32Int# :: Int# -> Int# narrow8Word# :: Word# -> Word# narrow16Word# :: Word# -> Word# narrow32Word# :: Word# -> Word# (>##) :: 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 <=## (+##) :: Double# -> Double# -> Double# infixl 6 +## (-##) :: Double# -> Double# -> Double# infixl 6 -## (*##) :: Double# -> Double# -> Double# infixl 7 *## -- | Warning: this can fail with an unchecked exception. (/##) :: Double# -> Double# -> Double# infixl 7 /## negateDouble# :: Double# -> Double# fabsDouble# :: Double# -> Double# -- | 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# double2Float# :: Double# -> Float# expDouble# :: Double# -> Double# expm1Double# :: Double# -> Double# -- | Warning: this can fail with an unchecked exception. logDouble# :: Double# -> Double# -- | Warning: this can fail with an unchecked exception. log1pDouble# :: Double# -> Double# sqrtDouble# :: Double# -> Double# sinDouble# :: Double# -> Double# cosDouble# :: Double# -> Double# tanDouble# :: Double# -> Double# -- | Warning: this can fail with an unchecked exception. asinDouble# :: Double# -> Double# -- | Warning: this can fail with an unchecked exception. acosDouble# :: Double# -> Double# atanDouble# :: Double# -> Double# sinhDouble# :: Double# -> Double# coshDouble# :: Double# -> Double# tanhDouble# :: Double# -> Double# asinhDouble# :: Double# -> Double# acoshDouble# :: Double# -> Double# atanhDouble# :: Double# -> Double# -- | Exponentiation. (**##) :: Double# -> Double# -> Double# -- | 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# #) -- | Decode Double# into mantissa and base-2 exponent. decodeDouble_Int64# :: Double# -> (# Int#, Int# #) gtFloat# :: Float# -> Float# -> Int# geFloat# :: Float# -> Float# -> Int# eqFloat# :: Float# -> Float# -> Int# neFloat# :: Float# -> Float# -> Int# ltFloat# :: Float# -> Float# -> Int# leFloat# :: Float# -> Float# -> Int# plusFloat# :: Float# -> Float# -> Float# minusFloat# :: Float# -> Float# -> Float# timesFloat# :: Float# -> Float# -> Float# -- | Warning: this can fail with an unchecked exception. divideFloat# :: Float# -> Float# -> Float# negateFloat# :: Float# -> Float# fabsFloat# :: 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# expFloat# :: Float# -> Float# expm1Float# :: Float# -> Float# -- | Warning: this can fail with an unchecked exception. logFloat# :: Float# -> Float# -- | Warning: this can fail with an unchecked exception. log1pFloat# :: Float# -> Float# sqrtFloat# :: Float# -> Float# sinFloat# :: Float# -> Float# cosFloat# :: Float# -> Float# tanFloat# :: Float# -> Float# -- | Warning: this can fail with an unchecked exception. asinFloat# :: Float# -> Float# -- | Warning: this can fail with an unchecked exception. acosFloat# :: Float# -> Float# atanFloat# :: Float# -> Float# sinhFloat# :: Float# -> Float# coshFloat# :: Float# -> Float# tanhFloat# :: Float# -> Float# asinhFloat# :: Float# -> Float# acoshFloat# :: Float# -> Float# atanhFloat# :: Float# -> Float# powerFloat# :: Float# -> Float# -> Float# float2Double# :: Float# -> Double# -- | Convert to integers. First Int# in result is the mantissa; -- second is the exponent. decodeFloat_Int# :: Float# -> (# Int#, Int# #) -- | 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# :: Int# -> a -> State# d -> (# State# d, MutableArray# d a #) sameMutableArray# :: MutableArray# d a -> MutableArray# d a -> Int# -- | Read from specified index of mutable array. Result is not yet -- evaluated. -- -- Warning: this can fail with an unchecked exception. readArray# :: MutableArray# d a -> Int# -> State# d -> (# State# d, a #) -- | Write to specified index of mutable array. -- -- Warning: this can fail with an unchecked exception. writeArray# :: MutableArray# d a -> Int# -> a -> State# d -> State# d -- | Return the number of elements in the array. sizeofArray# :: Array# a -> Int# -- | Return the number of elements in the array. sizeofMutableArray# :: MutableArray# d a -> Int# -- | 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# :: Array# a -> Int# -> (# a #) -- | Make a mutable array immutable, without copying. unsafeFreezeArray# :: MutableArray# d a -> State# d -> (# State# d, Array# a #) -- | Make an immutable array mutable, without copying. unsafeThawArray# :: Array# a -> State# d -> (# State# d, MutableArray# d 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. 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# :: Array# 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. 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# :: MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d -- | 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# :: Array# a -> Int# -> Int# -> 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# :: 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. freezeArray# :: 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. thawArray# :: Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# 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 lifted value makes this -- function harder to use correctly than casIntArray#. All of -- the difficulties of using reallyUnsafePtrEquality# correctly -- apply to casArray# as well. casArray# :: MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, 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. newSmallArray# :: Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #) sameSmallMutableArray# :: SmallMutableArray# d a -> SmallMutableArray# d a -> Int# -- | 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#. shrinkSmallMutableArray# :: SmallMutableArray# d a -> Int# -> 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# :: SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #) -- | Write to specified index of mutable array. -- -- Warning: this can fail with an unchecked exception. writeSmallArray# :: SmallMutableArray# d a -> Int# -> a -> State# d -> State# d -- | Return the number of elements in the array. sizeofSmallArray# :: SmallArray# a -> Int# -- | Return the number of elements in the array. Note that this is -- deprecated as it is unsafe in the presence of shrink and resize -- operations on the same small mutable array. sizeofSmallMutableArray# :: SmallMutableArray# d a -> Int# -- | Return the number of elements in the array. getSizeofSmallMutableArray# :: SmallMutableArray# d a -> State# d -> (# State# d, Int# #) -- | 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# :: SmallArray# a -> Int# -> (# a #) -- | Make a mutable array immutable, without copying. unsafeFreezeSmallArray# :: SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #) -- | Make an immutable array mutable, without copying. unsafeThawSmallArray# :: SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d 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. 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# :: SmallArray# 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. 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# :: SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d -- | 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# :: SmallArray# a -> Int# -> Int# -> 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# :: 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. freezeSmallArray# :: 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. thawSmallArray# :: SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) -- | Unsafe, machine-level atomic compare and swap on an element within an -- array. See the documentation of casArray#. casSmallArray# :: SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) -- | Create a new mutable byte array of specified size (in bytes), in the -- specified state thread. newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) -- | Create a mutable byte array that the GC guarantees not to move. newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) -- | Create a mutable byte array, aligned by the specified amount, that the -- GC guarantees not to move. newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) -- | Determine whether a MutableByteArray# is guaranteed not to -- move during GC. isMutableByteArrayPinned# :: MutableByteArray# d -> Int# -- | Determine whether a ByteArray# is guaranteed not to move -- during GC. isByteArrayPinned# :: ByteArray# -> Int# -- | Intended for use with pinned arrays; otherwise very unsafe! byteArrayContents# :: ByteArray# -> Addr# sameMutableByteArray# :: MutableByteArray# d -> MutableByteArray# d -> Int# -- | 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#. shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d -- | Resize (unpinned) mutable byte array to new specified size (in bytes). -- 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 #) -- | Make a mutable byte array immutable, without copying. unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) -- | Return the size of the array in bytes. sizeofByteArray# :: ByteArray# -> Int# -- | Return the size of the array in bytes. Note that this is deprecated as -- it is unsafe in the presence of shrink and resize operations on the -- same mutable byte array. sizeofMutableByteArray# :: MutableByteArray# d -> Int# -- | Return the number of elements in the array. getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #) -- | Read 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexCharArray# :: ByteArray# -> Int# -> Char# -- | Read 31-bit character; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. indexWideCharArray# :: ByteArray# -> Int# -> Char# -- | Warning: this can fail with an unchecked exception. indexIntArray# :: ByteArray# -> Int# -> Int# -- | Warning: this can fail with an unchecked exception. indexWordArray# :: ByteArray# -> Int# -> Word# -- | Warning: this can fail with an unchecked exception. indexAddrArray# :: ByteArray# -> Int# -> Addr# -- | Warning: this can fail with an unchecked exception. indexFloatArray# :: ByteArray# -> Int# -> Float# -- | Warning: this can fail with an unchecked exception. indexDoubleArray# :: ByteArray# -> Int# -> Double# -- | Warning: this can fail with an unchecked exception. indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a -- | Read 8-bit integer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexInt8Array# :: ByteArray# -> Int# -> Int# -- | Read 16-bit integer; offset in 16-bit words. -- -- Warning: this can fail with an unchecked exception. indexInt16Array# :: ByteArray# -> Int# -> Int# -- | Read 32-bit integer; offset in 32-bit words. -- -- Warning: this can fail with an unchecked exception. indexInt32Array# :: ByteArray# -> Int# -> Int# -- | Read 64-bit integer; offset in 64-bit words. -- -- Warning: this can fail with an unchecked exception. indexInt64Array# :: ByteArray# -> Int# -> Int# -- | Read 8-bit word; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8Array# :: ByteArray# -> Int# -> Word# -- | Read 16-bit word; offset in 16-bit words. -- -- Warning: this can fail with an unchecked exception. indexWord16Array# :: ByteArray# -> Int# -> Word# -- | Read 32-bit word; offset in 32-bit words. -- -- Warning: this can fail with an unchecked exception. indexWord32Array# :: ByteArray# -> Int# -> Word# -- | Read 64-bit word; offset in 64-bit words. -- -- Warning: this can fail with an unchecked exception. indexWord64Array# :: ByteArray# -> Int# -> Word# -- | Read 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# -- | Read 31-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# -- | Read address; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# -- | Read float; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# -- | Read double; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# -- | Read stable pointer; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a -- | Read 16-bit int; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int# -- | Read 32-bit int; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int# -- | Read 64-bit int; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int# -- | Read int; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# -- | Read 16-bit word; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word# -- | Read 32-bit word; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word# -- | Read 64-bit word; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word# -- | Read word; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# -- | Read 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) -- | Read 31-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 integer; offset in machine words. -- -- Warning: this can fail with an unchecked exception. readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Read word; offset in machine words. -- -- Warning: this can fail with an unchecked exception. readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) -- | Warning: this can fail with an unchecked exception. readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) -- | Warning: this can fail with an unchecked exception. readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) -- | Warning: this can fail with an unchecked exception. readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) -- | Warning: this can fail with an unchecked exception. readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) -- | Write 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d -- | Write 31-bit character; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeInt8Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeInt16Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeInt32Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeInt64Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord16Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord32Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord64Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> 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# -- | copyByteArray# src src_ofs dst dst_ofs n copies the range -- starting at offset src_ofs of length n 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 -- | Copy a range of the first MutableByteArray# to the specified region in -- the second MutableByteArray#. 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 -- | 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 -- | 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 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 -- | 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 -- | 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# #) -- | 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, 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 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, and offset in machine words, and a value to subtract, -- atomically subtract 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. fetchSubIntArray# :: 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 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. fetchAndIntArray# :: 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 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. fetchNandIntArray# :: 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 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. fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) -- | Given an array, and offset in machine words, and a value to XOR, -- atomically XOR 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. fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) -- | 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# d -> (# State# d, MutableArrayArray# d #) sameMutableArrayArray# :: MutableArrayArray# d -> MutableArrayArray# d -> Int# -- | Make a mutable array of arrays immutable, without copying. unsafeFreezeArrayArray# :: MutableArrayArray# d -> State# d -> (# State# d, ArrayArray# #) -- | Return the number of elements in the array. sizeofArrayArray# :: ArrayArray# -> Int# -- | Return the number of elements in the array. sizeofMutableArrayArray# :: MutableArrayArray# d -> Int# -- | Warning: this can fail with an unchecked exception. indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray# -- | Warning: this can fail with an unchecked exception. indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray# -- | Warning: this can fail with an unchecked exception. readByteArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (# State# d, ByteArray# #) -- | Warning: this can fail with an unchecked exception. readMutableByteArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #) -- | Warning: this can fail with an unchecked exception. readArrayArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (# State# d, ArrayArray# #) -- | Warning: this can fail with an unchecked exception. readMutableArrayArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (# State# d, MutableArrayArray# d #) -- | Warning: this can fail with an unchecked exception. writeByteArrayArray# :: MutableArrayArray# d -> Int# -> ByteArray# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeMutableByteArrayArray# :: MutableArrayArray# d -> Int# -> MutableByteArray# d -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeArrayArrayArray# :: MutableArrayArray# d -> Int# -> ArrayArray# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeMutableArrayArrayArray# :: MutableArrayArray# d -> Int# -> MutableArrayArray# d -> State# d -> State# d -- | 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. -- -- Warning: this can fail with an unchecked exception. copyArrayArray# :: ArrayArray# -> Int# -> MutableArrayArray# d -> Int# -> Int# -> State# d -> State# d -- | 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. -- -- Warning: this can fail with an unchecked exception. copyMutableArrayArray# :: MutableArrayArray# d -> Int# -> MutableArrayArray# d -> Int# -> Int# -> State# d -> State# d plusAddr# :: Addr# -> Int# -> Addr# -- | Result is meaningless if two Addr#s are so far apart that -- their difference doesn't fit in an Int#. minusAddr# :: Addr# -> Addr# -> Int# -- | Return the remainder when the Addr# arg, treated like an -- Int#, is divided by the Int# arg. remAddr# :: Addr# -> Int# -> Int# -- | Coerce directly from address to int. addr2Int# :: Addr# -> Int# -- | Coerce directly from int to address. int2Addr# :: Int# -> Addr# gtAddr# :: Addr# -> Addr# -> Int# geAddr# :: Addr# -> Addr# -> Int# eqAddr# :: Addr# -> Addr# -> Int# neAddr# :: Addr# -> Addr# -> Int# ltAddr# :: Addr# -> Addr# -> Int# leAddr# :: Addr# -> Addr# -> Int# -- | Reads 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. indexCharOffAddr# :: Addr# -> Int# -> Char# -- | Reads 31-bit character; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. indexWideCharOffAddr# :: Addr# -> Int# -> Char# -- | Warning: this can fail with an unchecked exception. indexIntOffAddr# :: Addr# -> Int# -> Int# -- | Warning: this can fail with an unchecked exception. indexWordOffAddr# :: Addr# -> Int# -> Word# -- | Warning: this can fail with an unchecked exception. indexAddrOffAddr# :: Addr# -> Int# -> Addr# -- | Warning: this can fail with an unchecked exception. indexFloatOffAddr# :: Addr# -> Int# -> Float# -- | Warning: this can fail with an unchecked exception. indexDoubleOffAddr# :: Addr# -> Int# -> Double# -- | Warning: this can fail with an unchecked exception. indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -- | Warning: this can fail with an unchecked exception. indexInt8OffAddr# :: Addr# -> Int# -> Int# -- | Warning: this can fail with an unchecked exception. indexInt16OffAddr# :: Addr# -> Int# -> Int# -- | Warning: this can fail with an unchecked exception. indexInt32OffAddr# :: Addr# -> Int# -> Int# -- | Warning: this can fail with an unchecked exception. indexInt64OffAddr# :: Addr# -> Int# -> Int# -- | Warning: this can fail with an unchecked exception. indexWord8OffAddr# :: Addr# -> Int# -> Word# -- | Warning: this can fail with an unchecked exception. indexWord16OffAddr# :: Addr# -> Int# -> Word# -- | Warning: this can fail with an unchecked exception. indexWord32OffAddr# :: Addr# -> Int# -> Word# -- | Warning: this can fail with an unchecked exception. indexWord64OffAddr# :: Addr# -> Int# -> Word# -- | Reads 8-bit character; offset in bytes. -- -- Warning: this can fail with an unchecked exception. readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) -- | Reads 31-bit character; offset in 4-byte words. -- -- Warning: this can fail with an unchecked exception. readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) -- | Warning: this can fail with an unchecked exception. readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) -- | Warning: this can fail with an unchecked exception. readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) -- | Warning: this can fail with an unchecked exception. readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) -- | Warning: this can fail with an unchecked exception. readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) -- | Warning: this can fail with an unchecked exception. readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) -- | Warning: this can fail with an unchecked exception. readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) -- | Warning: this can fail with an unchecked exception. writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeInt8OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeInt16OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeInt32OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeInt64OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord8OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord16OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord32OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d -- | Warning: this can fail with an unchecked exception. writeWord64OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d -- | Create MutVar# with specified initial value in specified -- state thread. newMutVar# :: a -> State# d -> (# State# d, MutVar# d a #) -- | Read contents of MutVar#. Result is not yet evaluated. readMutVar# :: MutVar# d a -> State# d -> (# State# d, a #) -- | Write contents of MutVar#. writeMutVar# :: MutVar# d a -> a -> State# d -> State# d sameMutVar# :: MutVar# d a -> MutVar# d a -> Int# -- | Modify the contents of a MutVar#, returning the previous -- contents and the result of applying the given function to the previous -- contents. Note that this isn't strictly speaking the correct type for -- this function; it should really be MutVar# s a -> (a -> -- (a,b)) -> State# s -> (# State# s, a, (a, b) #), but we -- don't know about pairs here. -- -- Warning: this can fail with an unchecked exception. atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #) -- | 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 #) casMutVar# :: MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #) catch# :: (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) -- | Warning: this can fail with an unchecked exception. raise# :: forall b (q :: RuntimeRep) (a :: TYPE q). b -> a -- | Raise a 'DivideByZero' arithmetic exception. raiseDivZero# :: forall (q :: RuntimeRep) (a :: TYPE q). Void# -> a -- | Raise an 'Underflow' arithmetic exception. raiseUnderflow# :: forall (q :: RuntimeRep) (a :: TYPE q). Void# -> a -- | Raise an 'Overflow' arithmetic exception. raiseOverflow# :: forall (q :: RuntimeRep) (a :: TYPE q). Void# -> a raiseIO# :: a -> State# RealWorld -> (# State# RealWorld, b #) maskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) maskUninterruptible# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) unmaskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) getMaskingState# :: State# RealWorld -> (# State# RealWorld, Int# #) atomically# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) retry# :: State# RealWorld -> (# State# RealWorld, a #) catchRetry# :: (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) catchSTM# :: (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) -- | Create a new TVar# holding a specified initial value. newTVar# :: a -> State# d -> (# State# d, TVar# d a #) -- | Read contents of TVar#. Result is not yet evaluated. readTVar# :: TVar# d a -> State# d -> (# State# d, a #) -- | Read contents of TVar# outside an STM transaction readTVarIO# :: TVar# d a -> State# d -> (# State# d, a #) -- | Write contents of TVar#. writeTVar# :: TVar# d a -> a -> State# d -> State# d sameTVar# :: TVar# d a -> TVar# d a -> Int# -- | Create new MVar#; initially empty. newMVar# :: State# d -> (# State# d, MVar# d a #) -- | If MVar# is empty, block until it becomes full. Then remove -- and return its contents, and set it empty. takeMVar# :: MVar# d a -> State# d -> (# State# d, a #) -- | 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# :: MVar# d a -> State# d -> (# State# d, Int#, a #) -- | If MVar# is full, block until it becomes empty. Then store -- value arg as its new contents. putMVar# :: MVar# d a -> a -> State# d -> State# d -- | If MVar# is full, immediately return with integer 0. -- Otherwise, store value arg as MVar#'s new contents, and -- return with integer 1. tryPutMVar# :: MVar# d a -> a -> State# d -> (# State# d, Int# #) -- | 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# :: MVar# d a -> State# d -> (# State# d, a #) -- | If MVar# is empty, immediately return with integer 0 and -- value undefined. Otherwise, return with integer 1 and contents of -- MVar#. tryReadMVar# :: MVar# d a -> State# d -> (# State# d, Int#, a #) sameMVar# :: MVar# d a -> MVar# d a -> Int# -- | Return 1 if MVar# is empty; 0 otherwise. isEmptyMVar# :: MVar# d a -> State# d -> (# State# d, Int# #) -- | Sleep specified number of microseconds. delay# :: Int# -> State# d -> State# d -- | Block until input is available on specified file descriptor. waitRead# :: Int# -> State# d -> State# d -- | Block until output is possible on specified file descriptor. waitWrite# :: Int# -> State# d -> State# d fork# :: a -> State# RealWorld -> (# State# RealWorld, ThreadId# #) forkOn# :: Int# -> a -> State# RealWorld -> (# State# RealWorld, ThreadId# #) killThread# :: ThreadId# -> a -> State# RealWorld -> State# RealWorld yield# :: State# RealWorld -> State# RealWorld myThreadId# :: State# RealWorld -> (# State# RealWorld, ThreadId# #) labelThread# :: ThreadId# -> Addr# -> State# RealWorld -> State# RealWorld isCurrentThreadBound# :: State# RealWorld -> (# State# RealWorld, Int# #) noDuplicate# :: State# d -> State# d threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #) -- | 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 (q :: RuntimeRep) (a :: TYPE q) b c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) mkWeakNoFinalizer# :: forall (q :: RuntimeRep) (a :: TYPE q) b. a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) -- | 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# :: Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #) deRefWeak# :: Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #) -- | 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# :: Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) touch# :: forall (q :: RuntimeRep) (a :: TYPE q). a -> State# RealWorld -> State# RealWorld makeStablePtr# :: a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #) deRefStablePtr# :: StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #) eqStablePtr# :: StablePtr# a -> StablePtr# a -> Int# makeStableName# :: a -> State# RealWorld -> (# State# RealWorld, StableName# a #) eqStableName# :: StableName# a -> StableName# b -> Int# stableNameToInt# :: StableName# a -> Int# -- | 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# #) -- | 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 -- | Returns 1# if the object is contained in the CNF, 0# otherwise. compactContains# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, Int# #) -- | Returns 1# if the object is in any CNF at all, 0# otherwise. compactContainsAny# :: a -> State# RealWorld -> (# State# RealWorld, Int# #) -- | 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# #) -- | 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# #) -- | 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 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# #) -- | 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 #) -- | Like compactAdd#, but retains sharing and cycles during -- compaction. compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) -- | Return the total capacity (in bytes) of all the compact blocks in the -- CNF. compactSize# :: Compact# -> State# RealWorld -> (# State# RealWorld, Word# #) -- | Returns 1# if the given pointers are equal and 0# -- otherwise. -- -- Warning: this can fail with an unchecked exception. reallyUnsafePtrEquality# :: a -> a -> Int# par# :: a -> Int# spark# :: a -> State# d -> (# State# d, a #) seq# :: a -> State# d -> (# State# d, a #) getSpark# :: State# d -> (# State# d, Int#, a #) -- | Returns the number of sparks in the local spark pool. numSparks# :: State# d -> (# State# d, Int# #) dataToTag# :: a -> Int# tagToEnum# :: Int# -> a -- | Convert an Addr# to a followable Any type. addrToAny# :: Addr# -> (# 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# #) -- | Wrap a BCO in a AP_UPD thunk which will be updated with the -- value of the BCO when evaluated. mkApUpd0# :: BCO -> (# a #) -- | 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 #) -- | 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 #) -- | closureSize# closure returns the size of the given closure in -- machine words. closureSize# :: a -> Int# getApStackVal# :: a -> Int# -> (# Int#, b #) getCCSOf# :: a -> State# d -> (# State# d, Addr# #) -- | 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# #) -- | 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 #) -- | 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 -- | Emits an event via the RTS tracing framework. The contents of the -- event is the binary object passed as the first argument with the 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 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 -- | Sets the allocation counter for the current thread to the given value. setThreadAllocationCounter# :: Int# -> State# RealWorld -> State# RealWorld -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt8X16# :: Int# -> Int8X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt16X8# :: Int# -> Int16X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt32X4# :: Int# -> Int32X4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt64X2# :: Int# -> Int64X2# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt8X32# :: Int# -> Int8X32# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt16X16# :: Int# -> Int16X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt32X8# :: Int# -> Int32X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt64X4# :: Int# -> Int64X4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt8X64# :: Int# -> Int8X64# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt16X32# :: Int# -> Int16X32# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt32X16# :: Int# -> Int32X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastInt64X8# :: Int# -> Int64X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord8X16# :: Word# -> Word8X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord16X8# :: Word# -> Word16X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord32X4# :: Word# -> Word32X4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord64X2# :: Word# -> Word64X2# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord8X32# :: Word# -> Word8X32# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord16X16# :: Word# -> Word16X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord32X8# :: Word# -> Word32X8# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord64X4# :: Word# -> Word64X4# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord8X64# :: Word# -> Word8X64# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord16X32# :: Word# -> Word16X32# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord32X16# :: Word# -> Word32X16# -- | Broadcast a scalar to all elements of a vector. -- -- Warning: this is only available on LLVM. broadcastWord64X8# :: Word# -> Word64X8# -- | 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. broadcastDoubleX2# :: Double# -> DoubleX2# -- | 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. broadcastDoubleX4# :: Double# -> DoubleX4# -- | 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. broadcastDoubleX8# :: Double# -> DoubleX8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt8X16# :: (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int8X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt16X8# :: (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int16X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt32X4# :: (# Int#, Int#, Int#, Int# #) -> Int32X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt64X2# :: (# Int#, Int# #) -> Int64X2# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt8X32# :: (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int8X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt16X16# :: (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int16X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt32X8# :: (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int32X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt64X4# :: (# Int#, Int#, Int#, Int# #) -> Int64X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt8X64# :: (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int8X64# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt16X32# :: (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int16X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt32X16# :: (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int32X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packInt64X8# :: (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int64X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord8X16# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word8X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord16X8# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word16X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord32X4# :: (# Word#, Word#, Word#, Word# #) -> Word32X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord64X2# :: (# Word#, Word# #) -> Word64X2# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord8X32# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word8X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord16X16# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word16X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord32X8# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word32X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord64X4# :: (# Word#, Word#, Word#, Word# #) -> Word64X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord8X64# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word8X64# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord16X32# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word16X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord32X16# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word32X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- Warning: this is only available on LLVM. packWord64X8# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word64X8# -- | 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. packDoubleX2# :: (# Double#, Double# #) -> DoubleX2# -- | 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. packDoubleX4# :: (# Double#, Double#, Double#, Double# #) -> DoubleX4# -- | 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. packDoubleX8# :: (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -> DoubleX8# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt8X16# :: Int8X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt16X8# :: Int16X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt32X4# :: Int32X4# -> (# Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt64X2# :: Int64X2# -> (# Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt8X32# :: Int8X32# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt16X16# :: Int16X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt32X8# :: Int32X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt64X4# :: Int64X4# -> (# Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt8X64# :: Int8X64# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt16X32# :: Int16X32# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt32X16# :: Int32X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackInt64X8# :: Int64X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord8X16# :: Word8X16# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord16X8# :: Word16X8# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord32X4# :: Word32X4# -> (# Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord64X2# :: Word64X2# -> (# Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord8X32# :: Word8X32# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord16X16# :: Word16X16# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord32X8# :: Word32X8# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord64X4# :: Word64X4# -> (# Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord8X64# :: Word8X64# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord16X32# :: Word16X32# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord32X16# :: Word32X16# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -- | Unpack the elements of a vector into an unboxed tuple. # -- -- Warning: this is only available on LLVM. unpackWord64X8# :: Word64X8# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -- | 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. unpackDoubleX2# :: DoubleX2# -> (# 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. unpackDoubleX4# :: DoubleX4# -> (# 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. unpackDoubleX8# :: DoubleX8# -> (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -- | 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# -> Int# -> Int# -> 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. insertInt16X8# :: Int16X8# -> Int# -> 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. insertInt32X4# :: Int32X4# -> Int# -> 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. insertInt64X2# :: Int64X2# -> Int# -> 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. insertInt8X32# :: Int8X32# -> Int# -> 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. insertInt16X16# :: Int16X16# -> Int# -> 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. insertInt32X8# :: Int32X8# -> Int# -> 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. insertInt64X4# :: Int64X4# -> Int# -> 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. insertInt8X64# :: Int8X64# -> Int# -> 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. insertInt16X32# :: Int16X32# -> Int# -> 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. insertInt32X16# :: Int32X16# -> Int# -> 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. insertInt64X8# :: Int64X8# -> Int# -> 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. insertWord8X16# :: Word8X16# -> Word# -> 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. insertWord16X8# :: Word16X8# -> Word# -> 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. insertWord32X4# :: Word32X4# -> Word# -> 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. insertWord64X2# :: Word64X2# -> Word# -> 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. insertWord8X32# :: Word8X32# -> Word# -> 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. insertWord16X16# :: Word16X16# -> Word# -> 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. insertWord32X8# :: Word32X8# -> Word# -> 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. insertWord64X4# :: Word64X4# -> Word# -> 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. insertWord8X64# :: Word8X64# -> Word# -> 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. insertWord16X32# :: Word16X32# -> Word# -> 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. insertWord32X16# :: Word32X16# -> Word# -> 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. insertWord64X8# :: Word64X8# -> Word# -> 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. 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. 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. 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. 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. 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. insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- | 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. plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# -- | 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. plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# -- | 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. plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# -- | 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. plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# -- | 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. plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# -- | 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. plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# -- | 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. plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# -- | 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. plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# -- | 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. plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# -- | 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. plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# -- | 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. plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# -- | 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. plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- | 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. plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -- | 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. plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -- | Add two vectors element-wise. -- -- Warning: this is only available on LLVM. plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- | 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. minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# -- | 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. minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# -- | 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. minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# -- | 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. minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# -- | 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. minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# -- | 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. minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# -- | 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. minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# -- | 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. minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# -- | 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. minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# -- | 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. minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# -- | 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. minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# -- | 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. minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- | 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. minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -- | 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. minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -- | Subtract two vectors element-wise. -- -- Warning: this is only available on LLVM. minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- | 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. timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# -- | 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. timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# -- | 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. timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# -- | 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. timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# -- | 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. timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# -- | 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. timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# -- | 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. timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# -- | 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. timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# -- | 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. timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# -- | 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. timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# -- | 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. timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# -- | 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. timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- | 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. timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -- | 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. timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -- | Multiply two vectors element-wise. -- -- Warning: this is only available on LLVM. timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -- | Divide two vectors element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- | 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. divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -- | 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. divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -- | Divide two vectors element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- | 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. quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# -- | 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. quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# -- | 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. quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# -- | 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. quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# -- | 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. quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# -- | 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. quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# -- | 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. quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# -- | 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. quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# -- | 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. quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# -- | 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. quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# -- | 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. quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# -- | Rounds towards zero element-wise. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. quotWord64X8# :: 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. remInt8X16# :: Int8X16# -> 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt8X16# :: Int8X16# -> Int8X16# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt16X8# :: Int16X8# -> Int16X8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt32X4# :: Int32X4# -> Int32X4# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt64X2# :: Int64X2# -> Int64X2# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt8X32# :: Int8X32# -> Int8X32# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt16X16# :: Int16X16# -> Int16X16# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt32X8# :: Int32X8# -> Int32X8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt64X4# :: Int64X4# -> Int64X4# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt8X64# :: Int8X64# -> Int8X64# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt16X32# :: Int16X32# -> Int16X32# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt32X16# :: Int32X16# -> Int32X16# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateInt64X8# :: Int64X8# -> Int64X8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateFloatX4# :: FloatX4# -> FloatX4# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateDoubleX2# :: DoubleX2# -> DoubleX2# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateFloatX8# :: FloatX8# -> FloatX8# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateDoubleX4# :: DoubleX4# -> DoubleX4# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateFloatX16# :: FloatX16# -> FloatX16# -- | Negate element-wise. -- -- Warning: this is only available on LLVM. negateDoubleX8# :: DoubleX8# -> DoubleX8# -- | 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# -- | 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8# -- | 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 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) -- | 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 -- | 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d -- | Reads vector; offset in bytes. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -- | 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. indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -- | 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. indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -- | 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. indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -- | 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. indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -- | 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. indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -- | 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. indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -- | 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. indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -- | 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. indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -- | 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. indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -- | 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. indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -- | 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. indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -- | 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. indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -- | 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. indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -- | 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. indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -- | 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) -- | 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 -- | 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d -- | 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# -- | 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> 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. readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #) -- | 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) -- | 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 -- | 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d -- | Reads vector; offset in scalar elements. -- -- Warning: this is only available on LLVM and can fail -- with an unchecked exception. indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -- | 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. indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -- | 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. indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -- | 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. indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -- | 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. indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -- | 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. indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -- | 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. indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -- | 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. indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -- | 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. indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -- | 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. indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -- | 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. indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -- | 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. indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -- | 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. indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -- | 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. indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -- | 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. indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -- | 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) -- | 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 -- | 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. 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. writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d prefetchAddr3# :: Addr# -> Int# -> State# d -> State# d prefetchValue3# :: a -> State# d -> State# d prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d prefetchAddr2# :: Addr# -> Int# -> State# d -> State# d prefetchValue2# :: a -> State# d -> State# d prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d prefetchAddr1# :: Addr# -> Int# -> State# d -> State# d prefetchValue1# :: a -> State# d -> State# d prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d prefetchAddr0# :: Addr# -> Int# -> State# d -> State# d prefetchValue0# :: a -> State# d -> State# d -- | Shift the argument left by the specified number of bits (which must be -- non-negative). shiftL# :: Word# -> Int# -> Word# -- | Shift the argument right by the specified number of bits (which must -- be non-negative). The RL means "right, logical" (as opposed to -- RA for arithmetic) (although an arithmetic right shift wouldn't make -- sense for Word#) shiftRL# :: Word# -> Int# -> Word# -- | Shift the argument left by the specified number of bits (which must be -- non-negative). iShiftL# :: Int# -> Int# -> Int# -- | Shift the argument right (signed) by the specified number of bits -- (which must be non-negative). The RA means "right, arithmetic" -- (as opposed to RL for logical) iShiftRA# :: Int# -> Int# -> Int# -- | Shift the argument right (unsigned) by the specified number of bits -- (which must be non-negative). The RL means "right, logical" (as -- opposed to RA for arithmetic) iShiftRL# :: Int# -> Int# -> Int# uncheckedShiftL64# :: Word# -> Int# -> Word# uncheckedShiftRL64# :: Word# -> Int# -> Word# uncheckedIShiftL64# :: Int# -> Int# -> Int# uncheckedIShiftRA64# :: Int# -> Int# -> Int# -- | Alias for tagToEnum#. Returns True if its parameter is 1# and -- False if it is 0#. isTrue# :: Int# -> Bool -- | 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 -- -> ( 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 a. (forall b. (a -> b -> b) -> b -> b) -> [a] -- | A list producer that can be fused with foldr. This function is -- merely -- --
-- augment g xs = g (:) xs ---- -- but GHC's simplifier will transform an expression of the form -- foldr k z (augment g xs), which may arise after -- inlining, to g k (foldr k z xs), which avoids -- producing an intermediate list. augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] -- | Class for string-like datastructures; used by the overloaded string -- extension (-XOverloadedStrings in GHC). class IsString a fromString :: IsString a => String -> a 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 to the -- constant 5#. cstringLength# :: Addr# -> Int# breakpoint :: a -> a breakpointCond :: Bool -> a -> a -- | The call inline f arranges that f is inlined, -- regardless of its size. More precisely, the call inline f -- rewrites to the right-hand side of f's definition. This -- allows the programmer to control inlining from a particular call site -- rather than the definition site of the function (c.f. INLINE -- pragmas). -- -- This inlining occurs regardless of the argument to the call or the -- size of f's definition; it is unconditional. The main caveat -- is that f's definition must be visible to the compiler; it is -- therefore recommended to mark the function with an INLINABLE -- pragma at its definition so that GHC guarantees to record its -- unfolding regardless of size. -- -- If no inlining takes place, the inline function expands to the -- identity function in Phase zero, so its use imposes no overhead. inline :: a -> a -- | The 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. -- -- Like seq, the argument of lazy can have an unboxed -- type. 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 -- | 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 -- | 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. -- -- This function is runtime-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. coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). 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) -- | 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 -- | Lifted, heterogeneous equality. By lifted, we mean that it can be -- bogus (deferred type error). By heterogeneous, the two types -- a and b might have different kinds. Because -- ~~ can appear unexpectedly in error messages to users who do -- not care about the difference between heterogeneous equality -- ~~ and homogeneous equality ~, this is printed as -- ~ unless -fprint-equality-relations is set. class a ~# b => (a :: k0) ~~ (b :: k1) data TYPE (a :: RuntimeRep) -- | GHC maintains a property that the kind of all inhabited types (as -- distinct from type constructors or type-level data) tells us the -- runtime representation of values of that type. This datatype encodes -- the choice of runtime value. Note that TYPE is parameterised by -- RuntimeRep; this is precisely what we mean by the fact that a -- type's kind encodes the runtime representation. -- -- For boxed values (that is, values that are represented by a pointer), -- a further distinction is made, between lifted types (that contain ⊥), -- and unlifted ones (that don't). data RuntimeRep -- | a SIMD vector type VecRep :: VecCount -> VecElem -> RuntimeRep -- | An unboxed tuple of the given reps TupleRep :: [RuntimeRep] -> RuntimeRep -- | An unboxed sum of the given reps SumRep :: [RuntimeRep] -> RuntimeRep -- | lifted; represented by a pointer LiftedRep :: RuntimeRep -- | unlifted; represented by a pointer UnliftedRep :: RuntimeRep -- | signed, word-sized value IntRep :: RuntimeRep -- | signed, 8-bit value Int8Rep :: RuntimeRep -- | signed, 16-bit value Int16Rep :: RuntimeRep -- | signed, 32-bit value Int32Rep :: RuntimeRep -- | signed, 64-bit value (on 32-bit only) 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 (on 32-bit only) Word64Rep :: RuntimeRep -- | A pointer, but not to a Haskell value AddrRep :: RuntimeRep -- | a 32-bit floating point number FloatRep :: RuntimeRep -- | a 64-bit floating point number DoubleRep :: RuntimeRep -- | Length of a SIMD vector type data VecCount Vec2 :: VecCount Vec4 :: VecCount Vec8 :: VecCount Vec16 :: VecCount Vec32 :: VecCount Vec64 :: VecCount -- | Element of a SIMD vector type data VecElem Int8ElemRep :: VecElem Int16ElemRep :: VecElem Int32ElemRep :: VecElem Int64ElemRep :: VecElem Word8ElemRep :: VecElem Word16ElemRep :: VecElem Word32ElemRep :: VecElem Word64ElemRep :: VecElem FloatElemRep :: VecElem DoubleElemRep :: VecElem -- | The Down type allows you to reverse sort order conveniently. A -- value of type Down a contains a value of type -- a (represented as Down a). If a has -- an Ord instance associated with it then comparing two -- values thus wrapped will give you the opposite of their normal sort -- order. This is particularly useful when sorting in generalised list -- comprehensions, as in: then sortWith by Down x 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 sortWith :: Ord b => (a -> b) -> [a] -> [a] -- | the ensures that all the elements of the list are identical and -- then returns that unique element the :: Eq a => [a] -> a -- | Deprecated: Use traceEvent or traceEventIO traceEvent :: String -> IO () -- | Returns a [String] representing the current call stack. This -- can be useful for debugging. -- -- The implementation uses the call-stack simulation maintained by the -- profiler, so it only works if the program was compiled with -- -prof and contains suitable SCC annotations (e.g. by using -- -fprof-auto). Otherwise, the list returned is likely to be -- empty or uninformative. currentCallStack :: IO [String] -- | The kind of constraints, like Show a data Constraint -- | The type constructor Any is type to which you can unsafely -- coerce any lifted type, and back. More concretely, for a lifted type -- t and value x :: t, -- unsafeCoerce -- (unsafeCoerce x :: Any) :: t is equivalent to x. type family Any :: k -- | 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 family Item l; } -- | The fromList function constructs the structure l from -- the given list of Item l fromList :: IsList l => [Item l] -> l -- | The fromListN function takes the input list's length as a hint. -- Its behaviour should be equivalent to fromList. The hint can be -- used to construct the structure l more efficiently compared -- to fromList. If the given hint does not equal to the input -- list's length the behaviour of fromListN is not specified. fromListN :: IsList l => Int -> [Item l] -> l -- | The toList function extracts a list of Item l from the -- structure l. It should satisfy fromList . toList = id. toList :: IsList l => l -> [Item l] instance GHC.Exts.IsList [a] instance GHC.Exts.IsList (Control.Applicative.ZipList a) instance GHC.Exts.IsList (GHC.Base.NonEmpty a) instance GHC.Exts.IsList Data.Version.Version instance GHC.Exts.IsList GHC.Stack.Types.CallStack -- | 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. class Functor f -- | Using ApplicativeDo: 'fmap f as' can be -- understood as the do expression -- --
-- do a <- as -- pure (f a) ---- -- with an inferred Functor constraint. 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. -- -- Using ApplicativeDo: 'a <$ bs' can be -- understood as the do expression -- --
-- do bs -- pure a ---- -- with an inferred Functor constraint. (<$) :: 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: -- --
-- do a <- as -- bs a --(>>=) :: forall a b. Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. -- -- 'as >> bs' can be understood as the do -- expression -- --
-- do as -- bs --(>>) :: forall a b. 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 --class Monad m => MonadFail m fail :: MonadFail m => String -> m a -- | Monads that also support choice and failure. class (Alternative m, Monad m) => MonadPlus m -- | The identity of mplus. It should also satisfy the equations -- --
-- mzero >>= f = mzero -- v >> mzero = mzero ---- -- 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_. mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and ignore the results. For a version that -- doesn't ignore the results see mapM. -- -- As of base 4.8.0.0, mapM_ is just traverse_, specialized -- to Monad. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () -- | forM is mapM with its arguments flipped. For a version -- that ignores the results see forM_. forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) -- | forM_ is mapM_ with its arguments flipped. For a version -- that doesn't ignore the results see forM. -- -- As of base 4.8.0.0, forM_ is just for_, specialized to -- Monad. forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m () -- | Evaluate each monadic action in the structure from left to right, and -- collect the results. For a version that ignores the results see -- sequence_. sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) -- | Evaluate each monadic action in the structure from left to right, and -- ignore the results. For a version that doesn't ignore the results see -- sequence. -- -- As of base 4.8.0.0, sequence_ is just sequenceA_, -- specialized to Monad. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | Left-to-right 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. -- -- Using ApplicativeDo: 'forever as' can be -- understood as the pseudo-do expression -- --
-- do as -- as -- .. ---- -- with as repeating. -- --
-- 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 --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. -- -- Using ApplicativeDo: 'void as' can be -- understood as the do expression -- --
-- do as -- pure () ---- -- with an inferred Functor constraint. -- --
-- >>> 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 ---- --
-- 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, generalizing concat. As of -- base 4.8.0.0, msum is just asum, specialized to -- MonadPlus. msum :: (Foldable t, MonadPlus m) => t (m a) -> m a -- | Direct MonadPlus equivalent of filter. -- --
-- filter = ( mfilter :: (a -> Bool) -> [a] -> [a] ) ---- -- 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 n times, -- gathering the results. -- -- Using ApplicativeDo: 'replicateM 5 as' can be -- understood as the do expression -- --
-- do a1 <- as -- a2 <- as -- a3 <- as -- a4 <- as -- a5 <- as -- pure [a1,a2,a3,a4,a5] ---- -- Note the Applicative constraint. replicateM :: Applicative m => Int -> m a -> m [a] -- | Like replicateM, but discards the result. replicateM_ :: Applicative m => Int -> m a -> m () -- | Conditional failure of Alternative computations. Defined by -- --
-- guard True = pure () -- guard False = empty ---- --
-- >>> 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. -- --
-- >>> 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"). -- --
-- >>> 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. -- --
-- >>> let s = Left "foo" :: Either String Int -- -- >>> let n = Right 3 :: Either String Int -- -- >>> either length (*2) s -- 3 -- -- >>> either length (*2) n -- 6 --either :: (a -> c) -> (b -> c) -> Either a b -> c data Ordering LT :: Ordering EQ :: Ordering GT :: Ordering -- | The character type Char is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. -- characters, see http://www.unicode.org/ for details). This set -- extends the ISO 8859-1 (Latin-1) character set (the first 256 -- characters), which is itself an extension of the ASCII character set -- (the first 128 characters). A character literal in Haskell has type -- Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char -- | A String is a list of characters. String constants in Haskell -- are values of type String. -- -- See Data.List for operations on lists. type String = [Char] -- | Extract the first component of a pair. fst :: (a, b) -> a -- | Extract the second component of a pair. snd :: (a, b) -> b -- | curry converts an uncurried function to a curried function. -- --
-- >>> curry fst 1 2 -- 1 --curry :: ((a, b) -> c) -> a -> b -> c -- | uncurry converts a curried function to a function on pairs. -- --
-- >>> 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, == -- is customarily expected to implement an equivalence relationship where -- two values comparing equal are indistinguishable by "public" -- functions, with a "public" function being one not allowing to see -- implementation details. For example, for a type representing -- non-normalised natural numbers modulo 100, a "public" function doesn't -- make the difference between 1 and 201. It is expected to have the -- following properties: -- --
-- 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 4 :: [Integer] = [4,5,6,7,...]
enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: -- Int]
enumFromThen 4 6 :: [Integer] = [4,6,8,10...]
enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: -- Int]
enumFromTo 6 10 :: [Int] = [6,7,8,9,10]
enumFromTo 42 1 :: [Integer] = []
enumFromThenTo 4 2 -6 :: [Integer] = -- [4,2,0,-2,-4,-6]
enumFromThenTo 6 8 2 :: [Int] = []
-- 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 * 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: -- --
-- (x `quot` y)*y + (x `rem` y) == x --rem :: Integral a => a -> a -> a -- | integer division truncated toward negative infinity div :: Integral a => a -> a -> a -- | integer modulus, satisfying -- --
-- (x `div` y)*y + (x `mod` y) == x --mod :: Integral a => a -> a -> a -- | simultaneous quot and rem quotRem :: Integral a => a -> a -> (a, a) -- | simultaneous div and mod divMod :: Integral a => a -> a -> (a, a) -- | conversion to Integer toInteger :: Integral a => a -> Integer 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: -- --
-- >>> [1,2,3] <> [4,5,6] -- [1,2,3,4,5,6] --(<>) :: 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: -- --
-- >>> "Hello world" <> mempty -- "Hello world" --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. class Functor f -- | Using ApplicativeDo: 'fmap f as' can be -- understood as the do expression -- --
-- do a <- as -- pure (f a) ---- -- with an inferred Functor constraint. 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. -- -- Using ApplicativeDo: 'a <$ bs' can be -- understood as the do expression -- --
-- do bs -- pure a ---- -- with an inferred Functor constraint. (<$) :: 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. -- --
-- >>> 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 -- --
-- (<*>) = liftA2 id ---- --
-- liftA2 f x y = f <$> x <*> y ---- -- Further, any definition must satisfy the following: -- --
pure id <*> v = -- v
pure (.) <*> u -- <*> v <*> w = u <*> (v -- <*> w)
pure f <*> -- pure x = pure (f x)
u <*> pure y = -- pure ($ y) <*> u
-- forall x y. p (q x y) = f x . g y ---- -- it follows from the above that -- --
-- liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v ---- -- If f is also a Monad, it should satisfy -- -- -- -- (which implies that pure and <*> satisfy the -- applicative functor laws). class Functor f => Applicative f -- | Lift a value. pure :: Applicative f => a -> f a -- | Sequential application. -- -- A few functors support an implementation of <*> that is -- more efficient than the default one. -- -- Using ApplicativeDo: 'fs <*> as' can be -- understood as the do expression -- --
-- do f <- fs -- a <- as -- pure (f a) --(<*>) :: Applicative f => f (a -> b) -> f a -> f b -- | Sequence actions, discarding the value of the first argument. -- -- 'as *> bs' can be understood as the do -- expression -- --
-- do as -- bs ---- -- This is a tad complicated for our ApplicativeDo extension -- which will give it a Monad constraint. For an -- Applicative constraint we write it of the form -- --
-- do _ <- as -- b <- bs -- pure b --(*>) :: Applicative f => f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. -- -- Using ApplicativeDo: 'as <* bs' can be -- understood as the do expression -- --
-- do a <- as -- bs -- pure a --(<*) :: 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: -- --
-- do a <- as -- bs a --(>>=) :: forall a b. Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. -- -- 'as >> bs' can be understood as the do -- expression -- --
-- do as -- bs --(>>) :: forall a b. 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 --class Monad m => MonadFail m 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. -- -- As of base 4.8.0.0, mapM_ is just traverse_, specialized -- to Monad. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () -- | Evaluate each monadic action in the structure from left to right, and -- ignore the results. For a version that doesn't ignore the results see -- sequence. -- -- As of base 4.8.0.0, sequence_ is just sequenceA_, -- specialized to Monad. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | Data structures that can be folded. -- -- For example, given a data type -- --
-- data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) ---- -- a suitable instance would be -- --
-- instance Foldable Tree where -- foldMap f Empty = mempty -- foldMap f (Leaf x) = f x -- foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r ---- -- This is suitable even for abstract types, as the monoid is assumed to -- satisfy the monoid laws. Alternatively, one could define -- foldr: -- --
-- instance Foldable Tree where -- foldr f z Empty = z -- foldr f z (Leaf x) = f x z -- foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l ---- -- Foldable instances are expected to satisfy the following -- laws: -- --
-- foldr f z t = appEndo (foldMap (Endo . f) t ) z ---- --
-- foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z ---- --
-- fold = foldMap id ---- --
-- length = getSum . foldMap (Sum . const 1) ---- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
-- sum = getSum . foldMap Sum ---- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
-- foldMap f = fold . fmap f ---- -- which implies that -- --
-- foldMap f . fmap g = foldMap (f . g) --class Foldable t -- | Map each element of the structure to a monoid, and combine the -- results. -- --
-- >>> foldMap 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] ---- -- Infinite structures never terminate: -- --
-- >>> foldMap Sum [1..] -- * Hangs forever * --foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | Right-associative fold of a structure. -- -- In the case of lists, foldr, when applied to a binary operator, -- a starting value (typically the right-identity of the operator), and a -- list, reduces the list using the binary operator, from right to left: -- --
-- foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) ---- -- Note that, since the head of the resulting expression is produced by -- an application of the operator to the first element of the list, -- foldr can produce a terminating expression from an infinite -- list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldr f z = foldr f z . toList ---- --
-- >>> foldr (||) False [False, True, False] -- True ---- --
-- >>> foldr (||) False [] -- False ---- --
-- >>> foldr (\nextChar reversedString -> reversedString ++ [nextChar]) "foo" ['a', 'b', 'c', 'd'] -- "foodcba" ---- --
-- >>> foldr (||) False (True : repeat False) -- True ---- -- But the following doesn't terminate: -- --
-- >>> foldr (||) False (repeat False ++ [True]) -- * Hangs forever * ---- --
-- >>> foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (repeat 1) -- [1,4,7,10,13,16,19,22,25,28,31,34,37,40,43... ---- --
-- >>> take 5 $ foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (repeat 1) -- [1,4,7,10,13] --foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Left-associative fold of a structure. -- -- In the case of lists, foldl, when applied to a binary operator, -- a starting value (typically the left-identity of the operator), and a -- list, reduces the list using the binary operator, from left to right: -- --
-- foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn ---- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldl' -- will diverge if given an infinite list. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is -- that latter does not force the "inner" results (e.g. z `f` x1 -- in the above example) before applying them to the operator (e.g. to -- (`f` x2)). This results in a thunk chain <math> -- elements long, which then must be evaluated from the outside-in. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
-- foldl f z = foldl f z . toList ---- --
-- >>> foldl (+) 42 (Node (Leaf 1) 3 (Node Empty 4 (Leaf 2))) -- 52 ---- --
-- >>> foldl (+) 42 Empty -- 42 ---- --
-- >>> foldl (\string nextElement -> nextElement : string) "abcd" (Node (Leaf 'd') 'e' (Node Empty 'f' (Leaf 'g'))) -- "gfedabcd" ---- -- Left-folding infinite structures never terminates: -- --
-- >>> let infiniteNode = Node Empty 1 infiniteNode in foldl (+) 42 infiniteNode -- * Hangs forever * ---- -- Evaluating the head of the result (when applicable) does not -- terminate, unlike foldr: -- --
-- >>> let infiniteNode = Node Empty 'd' infiniteNode in take 5 (foldl (\string nextElement -> nextElement : string) "abc" infiniteNode) -- * Hangs forever * --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. -- --
-- >>> 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 ---- --
-- >>> 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. -- --
-- >>> 3 `elem` [] -- False ---- --
-- >>> 3 `elem` [1,2] -- False ---- --
-- >>> 3 `elem` [1,2,3,4,5] -- True ---- -- For infinite structures, elem terminates if the 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. -- --
-- >>> maximum [1..10] -- 10 ---- --
-- >>> maximum [] -- *** Exception: Prelude.maximum: empty list ---- --
-- >>> maximum Nothing -- *** Exception: maximum: empty structure --maximum :: forall a. (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 -- --
-- >>> minimum [1..10] -- 1 ---- --
-- >>> minimum [] -- *** Exception: Prelude.minimum: empty list ---- --
-- >>> minimum Nothing -- *** Exception: minimum: empty structure --minimum :: forall a. (Foldable t, Ord a) => t a -> a -- | The sum function computes the sum of the numbers of a -- structure. -- --
-- >>> sum [] -- 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. -- --
-- >>> 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 traversed from left -- to right. -- -- A definition of traverse must satisfy the following laws: -- --
-- t :: (Applicative f, Applicative g) => f a -> g a ---- -- preserving the Applicative operations, i.e. -- --
-- t (pure x) = pure x -- t (f <*> x) = t f <*> t x ---- -- and the identity functor Identity and composition functors -- Compose are from Data.Functor.Identity and -- Data.Functor.Compose. -- -- A result of the naturality law is a purity law for traverse -- --
-- traverse pure = pure ---- -- (The naturality law is implied by parametricity and thus so is the -- purity law [1, p15].) -- -- Instances are similar to Functor, e.g. given a data type -- --
-- data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) ---- -- a suitable instance would be -- --
-- instance Traversable Tree where -- traverse f Empty = pure Empty -- traverse f (Leaf x) = Leaf <$> f x -- traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r ---- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- --
-- id x = x --id :: a -> a -- | const x is a unary function which evaluates to x for -- all inputs. -- --
-- >>> const 42 "hello" -- 42 ---- --
-- >>> map (const 42) [0..3] -- [42,42,42,42] --const :: a -> b -> a -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 . -- | flip f takes its (first) two arguments in the reverse -- order of f. -- --
-- >>> flip (++) "hello" "world" -- "worldhello" --flip :: (a -> b -> c) -> b -> a -> c -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ has low, right-associative binding precedence, so it -- sometimes allows parentheses to be omitted; for example: -- --
-- f $ g $ h x = f (g (h x)) ---- -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. -- -- Note that ($) is levity-polymorphic in its result -- type, so that foo $ True where foo :: Bool -> -- Int# is well-typed. ($) :: forall r a (b :: TYPE r). (a -> b) -> a -> b infixr 0 $ -- | until p f yields the result of applying f -- until p holds. until :: (a -> Bool) -> (a -> a) -> a -> a -- | asTypeOf is a type-restricted version of const. It is -- usually used as an infix operator, and its typing forces its first -- argument (which is usually overloaded) to have the same type as the -- second. asTypeOf :: a -> a -> a -- | error stops execution and displays an error message. error :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => [Char] -> a -- | A variant of error that does not produce a stack trace. errorWithoutStackTrace :: forall (r :: RuntimeRep). forall (a :: TYPE r). [Char] -> a -- | A special case of error. It is expected that compilers will -- recognize this and insert error messages which are more appropriate to -- the context in which undefined appears. undefined :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => a -- | The value of seq a b is bottom if a is bottom, and -- otherwise equal to b. 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` -- | 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. ($!) :: forall r a (b :: TYPE r). (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, ...] ---- --
-- >>> map (+1) [1, 2, 3] -- [2,3,4] --map :: (a -> b) -> [a] -> [b] -- | Append two lists, i.e., -- --
-- [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] -- [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...] ---- -- If the first list is not finite, the result is the first list. (++) :: [a] -> [a] -> [a] infixr 5 ++ -- | <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] ---- --
-- >>> filter odd [1, 2, 3] -- [1,3] --filter :: (a -> Bool) -> [a] -> [a] -- | <math>. Extract the first element of a list, which must be -- non-empty. -- --
-- >>> head [1, 2, 3] -- 1 -- -- >>> head [1..] -- 1 -- -- >>> head [] -- Exception: Prelude.head: empty list --head :: [a] -> a -- | <math>. Extract the last element of a list, which must be finite -- and non-empty. -- --
-- >>> last [1, 2, 3] -- 3 -- -- >>> last [1..] -- * Hangs forever * -- -- >>> last [] -- Exception: Prelude.last: empty list --last :: [a] -> a -- | <math>. Extract the elements after the head of a list, which -- must be non-empty. -- --
-- >>> tail [1, 2, 3] -- [2,3] -- -- >>> tail [1] -- [] -- -- >>> tail [] -- Exception: Prelude.tail: empty list --tail :: [a] -> [a] -- | <math>. Return all the elements of a list except the last one. -- The list must be non-empty. -- --
-- >>> init [1, 2, 3] -- [1,2] -- -- >>> init [1] -- [] -- -- >>> init [] -- Exception: Prelude.init: empty list --init :: [a] -> [a] -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. -- --
-- >>> ['a', '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 --(!!) :: [a] -> Int -> a infixl 9 !! -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. -- --
-- >>> null [] -- True ---- --
-- >>> null [1] -- False ---- -- null terminates even for infinite structures: -- --
-- >>> null [1..] -- False --null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. -- --
-- >>> length [] -- 0 ---- --
-- >>> length ['a', 'b', 'c'] -- 3 -- -- >>> length [1..] -- * Hangs forever * --length :: Foldable t => t a -> Int -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. -- --
-- >>> 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. -- --
-- >>> 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 :: Foldable t => t Bool -> Bool -- | or returns the disjunction of a container of Bools. For the -- result to be False, the container must be finite; True, -- however, results from a True value finitely far from the left -- end. -- --
-- >>> or [] -- 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 :: Foldable t => t Bool -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> concat (Just [1, 2, 3]) -- [1,2,3] ---- --
-- >>> concat (Node (Leaf [1, 2, 3]) [4, 5] (Node Empty [6] (Leaf []))) -- [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. -- --
-- >>> concatMap (take 3) [[1..], [10..], [100..], [1000..]] -- [1,2,3,10,11,12,100,101,102,1000,1001,1002] ---- --
-- >>> concatMap (take 3) (Node (Leaf [1..]) [10..] Empty) -- [1,2,3,10,11,12] --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 ---- --
-- >>> 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"] -- -- >>> scanl (+) 0 [1..] -- * Hangs forever * --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, ...] ---- --
-- >>> 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] -- -- >>> scanl1 (+) [1..] -- * Hangs forever * --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. ---- --
-- >>> 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"] -- -- >>> scanr (+) 0 [1..] -- * Hangs forever * --scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | <math>. scanr1 is a variant of scanr that has no -- starting value argument. -- --
-- >>> 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] -- -- >>> scanr1 (+) [1..] -- * Hangs forever * --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), ...] ---- -- 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. -- --
-- >>> iterate not True -- [True,False,True,False... -- -- >>> iterate (+3) 42 -- [42,45,48,51,54,57,60,63... --iterate :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. -- --
-- >>> repeat 17 -- [17,17,17,17,17,17,17,17,17... --repeat :: a -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. -- --
-- >>> replicate 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. -- --
-- >>> cycle [] -- Exception: Prelude.cycle: empty list -- -- >>> cycle [42] -- [42,42,42,42,42,42,42,42,42,42... -- -- >>> cycle [2, 5, 7] -- [2,5,7,2,5,7,2,5,7,2,5,7... --cycle :: [a] -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n > length xs. -- --
-- >>> take 5 "Hello World!" -- "Hello" -- -- >>> take 3 [1,2,3,4,5] -- [1,2,3] -- -- >>> take 3 [1,2] -- [1,2] -- -- >>> take 3 [] -- [] -- -- >>> take (-1) [1,2] -- [] -- -- >>> take 0 [1,2] -- [] ---- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. take :: Int -> [a] -> [a] -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n > length -- xs. -- --
-- >>> drop 6 "Hello World!" -- "World!" -- -- >>> drop 3 [1,2,3,4,5] -- [4,5] -- -- >>> drop 3 [1,2] -- [] -- -- >>> drop 3 [] -- [] -- -- >>> drop (-1) [1,2] -- [1,2] -- -- >>> drop 0 [1,2] -- [1,2] ---- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. drop :: Int -> [a] -> [a] -- | takeWhile, applied to a predicate p and a list -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p. -- --
-- >>> takeWhile (< 3) [1,2,3,4,1,2,3,4] -- [1,2] -- -- >>> takeWhile (< 9) [1,2,3] -- [1,2,3] -- -- >>> takeWhile (< 0) [1,2,3] -- [] --takeWhile :: (a -> Bool) -> [a] -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. -- --
-- >>> dropWhile (< 3) [1,2,3,4,5,1,2,3] -- [3,4,5,1,2,3] -- -- >>> dropWhile (< 9) [1,2,3] -- [] -- -- >>> dropWhile (< 0) [1,2,3] -- [1,2,3] --dropWhile :: (a -> Bool) -> [a] -> [a] -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is longest prefix (possibly empty) -- of xs of elements that satisfy p and second element -- is the remainder of the list: -- --
-- >>> span (< 3) [1,2,3,4,1,2,3,4] -- ([1,2],[3,4,1,2,3,4]) -- -- >>> span (< 9) [1,2,3] -- ([1,2,3],[]) -- -- >>> span (< 0) [1,2,3] -- ([],[1,2,3]) ---- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | break, applied to a predicate p and a list -- xs, returns a tuple where first element is longest prefix -- (possibly empty) of xs of elements that do not satisfy -- p and second element is the remainder of the list: -- --
-- >>> break (> 3) [1,2,3,4,1,2,3,4] -- ([1,2,3],[4,1,2,3,4]) -- -- >>> break (< 9) [1,2,3] -- ([],[1,2,3]) -- -- >>> break (> 9) [1,2,3] -- ([1,2,3],[]) ---- -- break p is equivalent to span (not . -- p). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
-- >>> splitAt 6 "Hello World!" -- ("Hello ","World!") -- -- >>> splitAt 3 [1,2,3,4,5] -- ([1,2,3],[4,5]) -- -- >>> splitAt 1 [1,2,3] -- ([1],[2,3]) -- -- >>> splitAt 3 [1,2,3] -- ([1,2,3],[]) -- -- >>> splitAt 4 [1,2,3] -- ([1,2,3],[]) -- -- >>> splitAt 0 [1,2,3] -- ([],[1,2,3]) -- -- >>> splitAt (-1) [1,2,3] -- ([],[1,2,3]) ---- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) -- | notElem is the negation of elem. -- --
-- >>> 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. -- --
-- >>> 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 [1, 2] ['a', 'b'] -- [(1, 'a'), (2, 'b')] ---- -- 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 is right-lazy: -- --
-- >>> zip [] _|_ -- [] -- -- >>> zip _|_ [] -- _|_ ---- -- zip is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. 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..] ---- -- For example, zipWith (+) is applied to two lists to -- produce the list of corresponding sums: -- --
-- >>> zipWith (+) [1, 2, 3] [4, 5, 6] -- [5,7,9] ---- -- zipWith is right-lazy: -- --
-- >>> zipWith f [] _|_ -- [] ---- -- zipWith is capable of list fusion, but it is restricted to its -- first list argument and its resulting list. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | The zipWith3 function takes a function which combines three -- elements, as well as three lists and returns a list of 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..] --zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] -- | unzip transforms a list of pairs into a list of first -- components and a list of second components. -- --
-- >>> unzip [] -- ([],[]) -- -- >>> 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, analogous to unzip. -- --
-- >>> unzip3 [] -- ([],[],[]) -- -- >>> unzip3 [(1, 'a', True), (2, 'b', False)] -- ([1,2],"ab",[True,False]) --unzip3 :: [(a, b, c)] -> ([a], [b], [c]) -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. -- -- Note that after splitting the string at newline characters, the last -- part of the string is considered a line even if it doesn't end with a -- newline. For example, -- --
-- >>> lines "" -- [] ---- --
-- >>> lines "\n" -- [""] ---- --
-- >>> lines "one" -- ["one"] ---- --
-- >>> lines "one\n" -- ["one"] ---- --
-- >>> lines "one\n\n" -- ["one",""] ---- --
-- >>> lines "one\ntwo" -- ["one","two"] ---- --
-- >>> lines "one\ntwo\n" -- ["one","two"] ---- -- Thus lines s contains at least as many elements as -- newlines in s. lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space. -- --
-- >>> words "Lorem ipsum\ndolor" -- ["Lorem","ipsum","dolor"] --words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. -- --
-- >>> unlines ["Hello", "World", "!"] -- "Hello\nWorld\n!\n" --unlines :: [String] -> String -- | unwords is an inverse operation to words. It joins words -- with separating spaces. -- --
-- >>> unwords ["Lorem", "ipsum", "dolor"] -- "Lorem ipsum dolor" --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: -- --
-- 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, -- --
-- 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: -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Read in Haskell 2010 is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readsPrec d r = readParen (d > app_prec) -- (\r -> [(Leaf m,t) | -- ("Leaf",s) <- lex r, -- (m,t) <- readsPrec (app_prec+1) s]) r -- -- ++ readParen (d > up_prec) -- (\r -> [(u:^:v,w) | -- (u,s) <- readsPrec (up_prec+1) r, -- (":^:",t) <- lex s, -- (v,w) <- readsPrec (up_prec+1) t]) r -- -- where app_prec = 10 -- up_prec = 5 ---- -- Note that right-associativity of :^: is unused. -- -- The derived instance in GHC is equivalent to -- --
-- instance (Read a) => Read (Tree a) where -- -- readPrec = parens $ (prec app_prec $ do -- Ident "Leaf" <- lexP -- m <- step readPrec -- return (Leaf m)) -- -- +++ (prec up_prec $ do -- u <- step readPrec -- Symbol ":^:" <- lexP -- v <- step readPrec -- return (u :^: v)) -- -- where app_prec = 10 -- up_prec = 5 -- -- readListPrec = readListPrecDefault ---- -- Why do both readsPrec and readPrec exist, and why does -- GHC opt to implement readPrec in derived Read instances -- instead of readsPrec? The reason is that readsPrec is -- based on the ReadS type, and although ReadS is mentioned -- in the Haskell 2010 Report, it is not a very efficient parser data -- structure. -- -- readPrec, on the other hand, is based on a much more efficient -- ReadPrec datatype (a.k.a "new-style parsers"), but its -- definition relies on the use of the RankNTypes language -- extension. Therefore, readPrec (and its cousin, -- readListPrec) are marked as GHC-only. Nevertheless, it is -- recommended to use readPrec instead of readsPrec -- whenever possible for the efficiency improvements it brings. -- -- As mentioned above, derived Read instances in GHC will -- implement readPrec instead of readsPrec. The default -- implementations of readsPrec (and its cousin, readList) -- will simply use readPrec under the hood. If you are writing a -- Read instance by hand, it is recommended to write it like so: -- --
-- instance Read T where -- readPrec = ... -- readListPrec = readListPrecDefault --class Read a -- | attempts to parse a value from the front of the string, returning a -- list of (parsed value, remaining string) pairs. If there is no -- successful parse, the returned list is empty. -- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. readsPrec :: Read a => Int -> ReadS a -- | The method readList is provided to allow the programmer to give -- a specialised way of parsing lists of values. For example, this is -- used by the predefined Read instance of the Char type, -- where values of type String should be are expected to use -- double quotes, rather than square brackets. readList :: Read a => ReadS [a] -- | equivalent to readsPrec with a precedence of 0. reads :: Read a => ReadS a -- | readParen True p parses what p parses, -- but surrounded with parentheses. -- -- readParen False p parses what p -- parses, but optionally surrounded with parentheses. readParen :: Bool -> ReadS a -> ReadS a -- | The read function reads input from a string, which must be -- completely consumed by the input process. read 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: -- --
-- 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 IOException 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 IOException in the IO monad. ioError :: IOError -> IO a -- | Construct an IOException value with a string describing the -- error. The fail method of the IO instance of the -- Monad class raises a userError, thus: -- --
-- instance Monad IO where -- ... -- fail s = ioError (userError s) --userError :: String -> IOError -- | The representations of the types TyCon and TypeRep, and -- the function mkTyCon which is used by derived instances of -- Typeable to construct TyCons. -- -- Be warned, these functions can be used to construct ill-kinded type -- representations. module Type.Reflection.Unsafe -- | A concrete representation of a (monomorphic) type. TypeRep -- supports reasonably efficient equality. data TypeRep a -- | Construct a representation for a type application. mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep a :: k1 -> k2 -> TypeRep b :: k1 -> TypeRep (a b) -- | Exquisitely unsafe. mkTyCon :: String -> String -> String -> Int -> KindRep -> TyCon -- | Observe the Fingerprint of a type representation typeRepFingerprint :: TypeRep a -> Fingerprint someTypeRepFingerprint :: SomeTypeRep -> Fingerprint -- | The representation produced by GHC for conjuring up the kind of a -- TypeRep. data KindRep KindRepTyConApp :: TyCon -> [KindRep] -> KindRep KindRepVar :: !KindBndr -> KindRep KindRepApp :: KindRep -> KindRep -> KindRep KindRepFun :: KindRep -> KindRep -> KindRep KindRepTYPE :: !RuntimeRep -> KindRep KindRepTypeLitS :: TypeLitSort -> Addr# -> KindRep KindRepTypeLitD :: TypeLitSort -> [Char] -> KindRep pattern KindRepTypeLit :: TypeLitSort -> String -> KindRep data TypeLitSort TypeLitSymbol :: TypeLitSort TypeLitNat :: TypeLitSort data TyCon -- | Construct a representation for a type constructor applied at a -- monomorphic kind. -- -- Note that this is unsafe as it allows you to construct ill-kinded -- types. mkTrCon :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a tyConKindRep :: TyCon -> KindRep tyConKindArgs :: TyCon -> Int tyConFingerprint :: TyCon -> Fingerprint -- | Optional instance of Show for functions: -- --
-- instance Show (a -> b) where -- showsPrec _ _ = showString "<function>" --module Text.Show.Functions instance GHC.Show.Show (a -> b) -- | A C printf(3)-like formatter. This version has been extended -- by Bart Massey as per the recommendations of John Meacham and Simon -- Marlow -- http://comments.gmane.org/gmane.comp.lang.haskell.libraries/4726 -- to support extensible formatting for new datatypes. It has also been -- extended to support almost all C printf(3) syntax. module Text.Printf -- | Format a variable number of arguments with the C-style formatting -- string. -- --
-- >>> 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: -- --
-- 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)) -- | 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: -- --
-- 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: -- --
-- 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" == escapeArgs "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 mechasnism, -- and thus will always escape any whitespace, quotes, and backslashes. -- --
-- unescapeArgs "hello\\ \\\"world\\\"\\n" == escapeArgs "hello \"world\"" --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 r a | x r -> a -- | Selector function to extract the field from the record. getField :: HasField x r a => r -> a -- | This module defines the IsLabel class is used by the -- OverloadedLabels extension. See the wiki page for more -- details. -- -- When OverloadedLabels is enabled, if GHC sees an occurrence -- of the overloaded label syntax #foo, it is replaced with -- --
-- fromLabel @"foo" :: alpha ---- -- plus a wanted constraint IsLabel "foo" alpha. -- -- Note that if RebindableSyntax is enabled, the desugaring of -- overloaded label syntax will make use of whatever fromLabel -- is in scope. module GHC.OverloadedLabels class IsLabel (x :: Symbol) a fromLabel :: IsLabel x a => a -- | 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.Generics.Generic GHC.ByteOrder.ByteOrder instance GHC.Show.Show GHC.ByteOrder.ByteOrder instance GHC.Read.Read GHC.ByteOrder.ByteOrder instance GHC.Enum.Enum GHC.ByteOrder.ByteOrder instance GHC.Enum.Bounded GHC.ByteOrder.ByteOrder instance GHC.Classes.Ord GHC.ByteOrder.ByteOrder instance GHC.Classes.Eq GHC.ByteOrder.ByteOrder -- | 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.Ord Data.Unique.Unique instance GHC.Classes.Eq Data.Unique.Unique -- | Mutable references in the (strict) ST monad. module Data.STRef -- | a value of type STRef s a is a mutable variable in state -- thread s, containing a value of type a -- --
-- >>> :{ -- 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 -- --
-- 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 -- --
-- 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 -- --
-- 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 -- --
-- 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. class Functor f -- | Using ApplicativeDo: 'fmap f as' can be -- understood as the do expression -- --
-- do a <- as -- pure (f a) ---- -- with an inferred Functor constraint. 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. -- -- Using ApplicativeDo: 'a <$ bs' can be -- understood as the do expression -- --
-- do bs -- pure a ---- -- with an inferred Functor constraint. (<$) :: 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: -- --
-- do a <- as -- bs a --(>>=) :: forall a b. Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. -- -- 'as >> bs' can be understood as the do -- expression -- --
-- do as -- bs --(>>) :: forall a b. 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 -- | 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). -- --
-- 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 CPU time used during the post-mark pause phase of the concurrent -- nonmoving GC. [nonmoving_gc_sync_cpu_ns] :: RTSStats -> RtsTime -- | The time elapsed during the post-mark pause phase of the concurrent -- nonmoving GC. [nonmoving_gc_sync_elapsed_ns] :: RTSStats -> RtsTime -- | The maximum time elapsed during the post-mark pause phase of the -- concurrent nonmoving GC. [nonmoving_gc_sync_max_elapsed_ns] :: RTSStats -> RtsTime -- | The CPU time used during the post-mark pause phase of the concurrent -- nonmoving GC. [nonmoving_gc_cpu_ns] :: RTSStats -> RtsTime -- | The time elapsed during the post-mark pause phase of the concurrent -- nonmoving GC. [nonmoving_gc_elapsed_ns] :: RTSStats -> RtsTime -- | The maximum time elapsed during the post-mark pause phase of the -- concurrent nonmoving GC. [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 -> 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 (incliudes 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 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.Show.Show GHC.Stats.GCDetails instance GHC.Read.Read GHC.Stats.GCDetails instance GHC.Generics.Generic GHC.Stats.RTSStats instance GHC.Show.Show GHC.Stats.RTSStats instance GHC.Read.Read GHC.Stats.RTSStats -- | 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 -> Word32 -> Bool -> Bool -> Double -> Bool -> Bool -> RtsTime -> Bool -> Word -> Word -> Bool -> Word -> GCFlags [statsFile] :: GCFlags -> Maybe FilePath [giveStats] :: GCFlags -> GiveGCStats [maxStkSize] :: GCFlags -> Word32 [initialStkSize] :: GCFlags -> Word32 [stkChunkSize] :: GCFlags -> Word32 [stkChunkBufferSize] :: GCFlags -> Word32 [maxHeapSize] :: GCFlags -> Word32 [minAllocAreaSize] :: GCFlags -> Word32 [largeAllocLim] :: GCFlags -> Word32 [nurseryChunkSize] :: GCFlags -> Word32 [minOldGenSize] :: GCFlags -> Word32 [heapSizeSuggestion] :: GCFlags -> Word32 [heapSizeSuggestionAuto] :: GCFlags -> Bool [oldGenFactor] :: GCFlags -> Double [pcFreeHeap] :: GCFlags -> Double [generations] :: GCFlags -> Word32 [squeezeUpdFrames] :: GCFlags -> Bool -- | True = "compact all the time" [compact] :: GCFlags -> Bool [compactThreshold] :: GCFlags -> Double -- | use "mostly mark-sweep" instead of copying for the oldest generation [sweep] :: GCFlags -> Bool [ringBell] :: GCFlags -> Bool [idleGCDelayTime] :: GCFlags -> RtsTime [doIdleGC] :: GCFlags -> Bool -- | address to ask the OS for memory [heapBase] :: GCFlags -> Word [allocLimitGrace] :: GCFlags -> Word [numa] :: GCFlags -> Bool [numaMask] :: GCFlags -> Word -- | Parameters concerning context switching data ConcFlags ConcFlags :: RtsTime -> Int -> ConcFlags [ctxtSwitchTime] :: ConcFlags -> RtsTime [ctxtSwitchTicks] :: ConcFlags -> Int -- | Miscellaneous parameters data MiscFlags MiscFlags :: RtsTime -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Word -> 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 -- | 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 -- | Parameters of the cost-center profiler data ProfFlags ProfFlags :: DoHeapProfile -> RtsTime -> Word -> Bool -> Bool -> Word -> Word -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> ProfFlags [doHeapProfile] :: ProfFlags -> DoHeapProfile -- | time between samples [heapProfileInterval] :: ProfFlags -> RtsTime -- | ticks between samples (derived) [heapProfileIntervalTicks] :: ProfFlags -> Word [includeTSOs] :: ProfFlags -> Bool [showCCSOnException] :: ProfFlags -> Bool [maxRetainerSetSize] :: ProfFlags -> Word [ccsLength] :: ProfFlags -> Word [modSelector] :: ProfFlags -> Maybe String [descrSelector] :: ProfFlags -> Maybe String [typeSelector] :: ProfFlags -> Maybe String [ccSelector] :: ProfFlags -> Maybe String [ccsSelector] :: ProfFlags -> Maybe String [retainerSelector] :: ProfFlags -> Maybe String [bioSelector] :: ProfFlags -> Maybe String -- | Is event tracing enabled? data DoTrace -- | no tracing TraceNone :: DoTrace -- | send tracing events to the event log TraceEventLog :: DoTrace -- | send tracing events to stderr TraceStderr :: DoTrace -- | Parameters pertaining to event tracing data TraceFlags TraceFlags :: DoTrace -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> 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 getRTSFlags :: IO RTSFlags getGCFlags :: IO GCFlags getConcFlags :: IO ConcFlags getMiscFlags :: IO MiscFlags getDebugFlags :: IO DebugFlags getCCFlags :: IO CCFlags getProfFlags :: IO ProfFlags getTraceFlags :: IO TraceFlags getTickyFlags :: IO TickyFlags getParFlags :: IO ParFlags instance GHC.Generics.Generic GHC.RTS.Flags.GiveGCStats instance GHC.Show.Show GHC.RTS.Flags.GiveGCStats instance GHC.Generics.Generic GHC.RTS.Flags.GCFlags instance GHC.Show.Show GHC.RTS.Flags.GCFlags instance GHC.Generics.Generic GHC.RTS.Flags.ConcFlags instance GHC.Show.Show GHC.RTS.Flags.ConcFlags instance GHC.Generics.Generic GHC.RTS.Flags.MiscFlags instance GHC.Show.Show GHC.RTS.Flags.MiscFlags instance GHC.Generics.Generic GHC.RTS.Flags.DebugFlags instance GHC.Show.Show GHC.RTS.Flags.DebugFlags instance GHC.Generics.Generic GHC.RTS.Flags.DoCostCentres instance GHC.Show.Show GHC.RTS.Flags.DoCostCentres instance GHC.Generics.Generic GHC.RTS.Flags.CCFlags instance GHC.Show.Show GHC.RTS.Flags.CCFlags instance GHC.Generics.Generic GHC.RTS.Flags.DoHeapProfile instance GHC.Show.Show GHC.RTS.Flags.DoHeapProfile instance GHC.Generics.Generic GHC.RTS.Flags.ProfFlags instance GHC.Show.Show GHC.RTS.Flags.ProfFlags instance GHC.Generics.Generic GHC.RTS.Flags.DoTrace instance GHC.Show.Show GHC.RTS.Flags.DoTrace instance GHC.Generics.Generic GHC.RTS.Flags.TraceFlags instance GHC.Show.Show GHC.RTS.Flags.TraceFlags instance GHC.Generics.Generic GHC.RTS.Flags.TickyFlags instance GHC.Show.Show GHC.RTS.Flags.TickyFlags instance GHC.Generics.Generic GHC.RTS.Flags.ParFlags instance GHC.Show.Show GHC.RTS.Flags.ParFlags instance GHC.Generics.Generic GHC.RTS.Flags.RTSFlags instance GHC.Show.Show GHC.RTS.Flags.RTSFlags instance GHC.Enum.Enum GHC.RTS.Flags.DoTrace instance GHC.Enum.Enum GHC.RTS.Flags.DoHeapProfile instance GHC.Enum.Enum GHC.RTS.Flags.DoCostCentres instance GHC.Enum.Enum GHC.RTS.Flags.GiveGCStats -- | Internals of the ExecutionStack module module GHC.ExecutionStack.Internal -- | Location information about an address from a backtrace. data Location Location :: String -> String -> Maybe SrcLoc -> Location [objectName] :: Location -> String [functionName] :: Location -> String [srcLoc] :: Location -> Maybe SrcLoc -- | A location in the original program source. data SrcLoc SrcLoc :: String -> Int -> Int -> SrcLoc [sourceFile] :: SrcLoc -> String [sourceLine] :: SrcLoc -> Int [sourceColumn] :: SrcLoc -> Int -- | The state of the execution stack data StackTrace -- | List the frames of a stack trace. stackFrames :: StackTrace -> Maybe [Location] -- | How many stack frames in the given StackTrace stackDepth :: StackTrace -> Int -- | Get an execution stack. collectStackTrace :: IO (Maybe StackTrace) -- | Render a stacktrace as a string showStackFrames :: [Location] -> ShowS -- | Free the cached debug data. invalidateDebugCache :: IO () -- | This is a module for efficient stack traces. This stack trace -- implementation is considered low overhead. Basic usage looks like -- this: -- --
-- import GHC.ExecutionStack -- -- myFunction :: IO () -- myFunction = do -- putStrLn =<< showStackTrace ---- -- Your GHC must have been built with libdw support for this to -- work. -- --
-- user@host:~$ ghc --info | grep libdw -- ,("RTS expects libdw",YES) --module GHC.ExecutionStack -- | Location information about an address from a backtrace. data Location Location :: String -> String -> Maybe SrcLoc -> Location [objectName] :: Location -> String [functionName] :: Location -> String [srcLoc] :: Location -> Maybe SrcLoc -- | A location in the original program source. data SrcLoc SrcLoc :: String -> Int -> Int -> SrcLoc [sourceFile] :: SrcLoc -> String [sourceLine] :: SrcLoc -> Int [sourceColumn] :: SrcLoc -> Int -- | Get a trace of the current execution stack state. -- -- Returns Nothing if stack trace support isn't available on -- host machine. getStackTrace :: IO (Maybe [Location]) -- | Get a string representation of the current execution stack state. showStackTrace :: IO (Maybe String) -- | 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. inits :: Foldable f => f a -> NonEmpty [a] -- | The tails function takes a stream xs and returns all -- the suffixes of xs. tails :: Foldable f => f a -> NonEmpty [a] -- | iterate f x produces the infinite sequence of repeated -- applications of f to x. -- --
-- iterate f x = x :| [f x, f (f x), ..] --iterate :: (a -> a) -> a -> NonEmpty a -- | repeat x returns a constant stream, where all elements -- are equal to x. repeat :: a -> NonEmpty a -- | cycle xs returns the infinite repetition of -- xs: -- --
-- cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...] --cycle :: NonEmpty a -> NonEmpty a -- | unfold produces a new stream by repeatedly applying the -- unfolding function to the seed value to produce an element of type -- b and a new seed value. When the unfolding function returns -- Nothing instead of a new seed value, the stream ends. -- | Deprecated: Use unfoldr unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b -- | insert x xs inserts x into the last position -- in xs where it is still less than or equal to the next -- element. In particular, if the list is sorted beforehand, the result -- will also be sorted. insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a -- | some1 x sequences x one or more times. some1 :: Alternative f => f a -> f (NonEmpty a) -- | take n xs returns the first n elements of -- xs. take :: Int -> NonEmpty a -> [a] -- | drop n xs drops the first n elements off the -- front of the sequence xs. drop :: Int -> NonEmpty a -> [a] -- | splitAt n xs returns a pair consisting of the prefix -- of xs of length n and the remaining stream -- immediately following this prefix. -- --
-- 'splitAt' n xs == ('take' n xs, 'drop' n xs) -- xs == ys ++ zs where (ys, zs) = 'splitAt' n xs --splitAt :: Int -> NonEmpty a -> ([a], [a]) -- | takeWhile p xs returns the longest prefix of the -- stream xs for which the predicate p holds. takeWhile :: (a -> Bool) -> NonEmpty a -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. dropWhile :: (a -> Bool) -> NonEmpty a -> [a] -- | span p xs returns the longest prefix of xs -- that satisfies p, together with the remainder of the stream. -- --
-- 'span' p xs == ('takeWhile' p xs, 'dropWhile' p xs) -- xs == ys ++ zs where (ys, zs) = 'span' p xs --span :: (a -> Bool) -> NonEmpty a -> ([a], [a]) -- | The break p function is equivalent to span -- (not . p). break :: (a -> Bool) -> NonEmpty a -> ([a], [a]) -- | filter p xs removes any elements from xs that -- do not satisfy p. filter :: (a -> Bool) -> NonEmpty a -> [a] -- | The partition function takes a predicate p and a -- stream xs, and returns a pair of lists. The first list -- corresponds to the elements of xs for which p holds; -- the second corresponds to the elements of xs for which -- p does not hold. -- --
-- 'partition' p xs = ('filter' p xs, 'filter' (not . p) xs) --partition :: (a -> Bool) -> NonEmpty a -> ([a], [a]) -- | The group function takes a stream and returns a list of streams -- such that flattening the resulting list is equal to the argument. -- Moreover, each stream in the resulting list contains only equal -- elements. For example, in list notation: -- --
-- 'group' $ 'cycle' "Mississippi" -- = "M" : "i" : "ss" : "i" : "ss" : "i" : "pp" : "i" : "M" : "i" : ... --group :: (Foldable f, Eq a) => f a -> [NonEmpty a] -- | groupBy operates like group, but uses the provided -- equality predicate instead of ==. groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a] -- | groupWith operates like group, but uses the provided -- projection when comparing for equality groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a] -- | groupAllWith operates like groupWith, but sorts the list -- first so that each equivalence class has, at most, one list in the -- output groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a] -- | group1 operates like group, but uses the knowledge that -- its input is non-empty to produce guaranteed non-empty output. group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a) -- | groupBy1 is to group1 as groupBy is to -- group. groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a) -- | groupWith1 is to group1 as groupWith is to -- group groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) -- | groupAllWith1 is to groupWith1 as groupAllWith is -- to groupWith groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) -- | The 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. (!!) :: 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 :: [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: -- --
liftM (f *** g) (mzip -- ma mb) = mzip (liftM f ma) (liftM g -- mb)
-- instance (Eq1 f) => Eq1 (T f) where ... -- instance (Ord1 f) => Ord1 (T f) where ... -- instance (Read1 f) => Read1 (T f) where ... -- instance (Show1 f) => Show1 (T f) where ... ---- -- If these instances can be defined, defining instances of the base -- classes is mechanical: -- --
-- instance (Eq1 f, Eq a) => Eq (T f a) where (==) = eq1 -- instance (Ord1 f, Ord a) => Ord (T f a) where compare = compare1 -- instance (Read1 f, Read a) => Read (T f a) where -- readPrec = readPrec1 -- readListPrec = readListPrecDefault -- instance (Show1 f, Show a) => Show (T f a) where showsPrec = showsPrec1 --module Data.Functor.Classes -- | Lifting of the Eq class to unary type constructors. class Eq1 f -- | Lift an equality test through the type constructor. -- -- The function will usually be applied to an equality function, but the -- more general type ensures that the implementation uses it to compare -- elements of the first container with elements of the second. liftEq :: Eq1 f => (a -> b -> Bool) -> f a -> f b -> Bool -- | Lift the standard (==) function through the type -- constructor. eq1 :: (Eq1 f, Eq a) => f a -> f a -> Bool -- | Lifting of the Ord class to unary type constructors. class (Eq1 f) => Ord1 f -- | Lift a compare function through the type constructor. -- -- The function will usually be applied to a comparison function, but the -- more general type ensures that the implementation uses it to compare -- elements of the first container with elements of the second. liftCompare :: Ord1 f => (a -> b -> Ordering) -> f a -> f b -> Ordering -- | Lift the standard compare function through the type -- constructor. compare1 :: (Ord1 f, Ord a) => f a -> f a -> Ordering -- | Lifting of the Read class to unary type constructors. -- -- Both liftReadsPrec and liftReadPrec exist to match the -- interface provided in the Read type class, but it is -- recommended to implement Read1 instances using -- liftReadPrec as opposed to liftReadsPrec, since the -- former is more efficient than the latter. For example: -- --
-- instance Read1 T where -- liftReadPrec = ... -- liftReadListPrec = liftReadListPrecDefault ---- -- For more information, refer to the documentation for the Read -- class. class Read1 f -- | readsPrec function for an application of the type constructor -- based on readsPrec and readList functions for the -- argument type. liftReadsPrec :: Read1 f => (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) -- | readList function for an application of the type constructor -- based on readsPrec and readList functions for the -- argument type. The default implementation using standard list syntax -- is correct for most types. liftReadList :: Read1 f => (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] -- | readPrec function for an application of the type constructor -- based on readPrec and readListPrec functions for the -- argument type. liftReadPrec :: Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) -- | readListPrec function for an application of the type -- constructor based on readPrec and readListPrec functions -- for the argument type. -- -- The default definition uses liftReadList. Instances that define -- liftReadPrec should also define liftReadListPrec as -- liftReadListPrecDefault. liftReadListPrec :: Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec [f a] -- | Lift the standard readsPrec and readList functions -- through the type constructor. readsPrec1 :: (Read1 f, Read a) => Int -> ReadS (f a) -- | Lift the standard readPrec and readListPrec functions -- through the type constructor. readPrec1 :: (Read1 f, Read a) => ReadPrec (f a) -- | A possible replacement definition for the liftReadList method. -- This is only needed for Read1 instances where -- liftReadListPrec isn't defined as -- liftReadListPrecDefault. liftReadListDefault :: Read1 f => (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] -- | A possible replacement definition for the liftReadListPrec -- method, defined using liftReadPrec. liftReadListPrecDefault :: Read1 f => ReadPrec a -> ReadPrec [a] -> ReadPrec [f a] -- | Lifting of the Show class to unary type constructors. class Show1 f -- | showsPrec function for an application of the type constructor -- based on showsPrec and showList functions for the -- argument type. liftShowsPrec :: Show1 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS -- | showList function for an application of the type constructor -- based on showsPrec and showList functions for the -- argument type. The default implementation using standard list syntax -- is correct for most types. liftShowList :: Show1 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS -- | Lift the standard showsPrec and showList functions -- through the type constructor. showsPrec1 :: (Show1 f, Show a) => Int -> f a -> ShowS -- | Lifting of the Eq class to binary type constructors. class Eq2 f -- | Lift equality tests through the type constructor. -- -- The function will usually be applied to equality functions, but the -- more general type ensures that the implementation uses them to compare -- elements of the first container with elements of the second. liftEq2 :: Eq2 f => (a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool -- | Lift the standard (==) function through the type -- constructor. eq2 :: (Eq2 f, Eq a, Eq b) => f a b -> f a b -> Bool -- | Lifting of the Ord class to binary type constructors. class (Eq2 f) => Ord2 f -- | Lift compare functions through the type constructor. -- -- The function will usually be applied to comparison functions, but the -- more general type ensures that the implementation uses them to compare -- elements of the first container with elements of the second. liftCompare2 :: Ord2 f => (a -> b -> Ordering) -> (c -> d -> Ordering) -> f a c -> f b d -> Ordering -- | Lift the standard compare function through the type -- constructor. compare2 :: (Ord2 f, Ord a, Ord b) => f a b -> f a b -> Ordering -- | Lifting of the Read class to binary type constructors. -- -- Both liftReadsPrec2 and liftReadPrec2 exist to match the -- interface provided in the Read type class, but it is -- recommended to implement Read2 instances using -- liftReadPrec2 as opposed to liftReadsPrec2, since the -- former is more efficient than the latter. For example: -- --
-- instance Read2 T where -- liftReadPrec2 = ... -- liftReadListPrec2 = liftReadListPrec2Default ---- -- For more information, refer to the documentation for the Read -- class. @since 4.9.0.0 class Read2 f -- | readsPrec function for an application of the type constructor -- based on readsPrec and readList functions for the -- argument types. liftReadsPrec2 :: Read2 f => (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (f a b) -- | readList function for an application of the type constructor -- based on readsPrec and readList functions for the -- argument types. The default implementation using standard list syntax -- is correct for most types. liftReadList2 :: Read2 f => (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b] -- | readPrec function for an application of the type constructor -- based on readPrec and readListPrec functions for the -- argument types. liftReadPrec2 :: Read2 f => ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b) -- | readListPrec function for an application of the type -- constructor based on readPrec and readListPrec functions -- for the argument types. -- -- The default definition uses liftReadList2. Instances that -- define liftReadPrec2 should also define -- liftReadListPrec2 as liftReadListPrec2Default. liftReadListPrec2 :: Read2 f => ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b] -- | Lift the standard readsPrec function through the type -- constructor. readsPrec2 :: (Read2 f, Read a, Read b) => Int -> ReadS (f a b) -- | Lift the standard readPrec function through the type -- constructor. readPrec2 :: (Read2 f, Read a, Read b) => ReadPrec (f a b) -- | A possible replacement definition for the liftReadList2 method. -- This is only needed for Read2 instances where -- liftReadListPrec2 isn't defined as -- liftReadListPrec2Default. liftReadList2Default :: Read2 f => (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b] -- | A possible replacement definition for the liftReadListPrec2 -- method, defined using liftReadPrec2. liftReadListPrec2Default :: Read2 f => ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [f a b] -- | Lifting of the Show class to binary type constructors. class Show2 f -- | showsPrec function for an application of the type constructor -- based on showsPrec and showList functions for the -- argument types. liftShowsPrec2 :: Show2 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> f a b -> ShowS -- | showList function for an application of the type constructor -- based on showsPrec and showList functions for the -- argument types. The default implementation using standard list syntax -- is correct for most types. liftShowList2 :: Show2 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [f a b] -> ShowS -- | Lift the standard showsPrec function through the type -- constructor. showsPrec2 :: (Show2 f, Show a, Show b) => Int -> f a b -> ShowS -- | readsData p d is a parser for datatypes where each -- alternative begins with a data constructor. It parses the constructor -- and passes it to p. Parsers for various constructors can be -- constructed with readsUnary, readsUnary1 and -- readsBinary1, and combined with mappend from the -- Monoid class. readsData :: (String -> ReadS a) -> Int -> ReadS a -- | readData p is a parser for datatypes where each -- alternative begins with a data constructor. It parses the constructor -- and passes it to p. Parsers for various constructors can be -- constructed with readUnaryWith and readBinaryWith, and -- combined with '(|)' from the Alternative class. readData :: ReadPrec a -> ReadPrec a -- | readsUnaryWith rp n c n' matches the name of a unary -- data constructor and then parses its argument using rp. readsUnaryWith :: (Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t -- | readUnaryWith rp n c' matches the name of a unary data -- constructor and then parses its argument using rp. readUnaryWith :: ReadPrec a -> String -> (a -> t) -> ReadPrec t -- | readsBinaryWith rp1 rp2 n c n' matches the name of a -- binary data constructor and then parses its arguments using -- rp1 and rp2 respectively. readsBinaryWith :: (Int -> ReadS a) -> (Int -> ReadS b) -> String -> (a -> b -> t) -> String -> ReadS t -- | readBinaryWith rp1 rp2 n c' matches the name of a -- binary data constructor and then parses its arguments using -- rp1 and rp2 respectively. readBinaryWith :: ReadPrec a -> ReadPrec b -> String -> (a -> b -> t) -> ReadPrec t -- | showsUnaryWith sp n d x produces the string -- representation of a unary data constructor with name n and -- argument x, in precedence context d. showsUnaryWith :: (Int -> a -> ShowS) -> String -> Int -> a -> ShowS -- | showsBinaryWith sp1 sp2 n d x y produces the string -- representation of a binary data constructor with name n and -- arguments x and y, in precedence context d. showsBinaryWith :: (Int -> a -> ShowS) -> (Int -> b -> ShowS) -> String -> Int -> a -> b -> ShowS -- | readsUnary n c n' matches the name of a unary data -- constructor and then parses its argument using readsPrec. -- | Deprecated: Use readsUnaryWith to define -- liftReadsPrec readsUnary :: Read a => String -> (a -> t) -> String -> ReadS t -- | readsUnary1 n c n' matches the name of a unary data -- constructor and then parses its argument using readsPrec1. -- | Deprecated: Use readsUnaryWith to define -- liftReadsPrec readsUnary1 :: (Read1 f, Read a) => String -> (f a -> t) -> String -> ReadS t -- | readsBinary1 n c n' matches the name of a binary data -- constructor and then parses its arguments using readsPrec1. -- | Deprecated: Use readsBinaryWith to define -- liftReadsPrec readsBinary1 :: (Read1 f, Read1 g, Read a) => String -> (f a -> g a -> t) -> String -> ReadS t -- | showsUnary n d x produces the string representation of -- a unary data constructor with name n and argument x, -- in precedence context d. -- | Deprecated: Use showsUnaryWith to define -- liftShowsPrec showsUnary :: Show a => String -> Int -> a -> ShowS -- | showsUnary1 n d x produces the string representation -- of a unary data constructor with name n and argument -- x, in precedence context d. -- | Deprecated: Use showsUnaryWith to define -- liftShowsPrec showsUnary1 :: (Show1 f, Show a) => String -> Int -> f a -> ShowS -- | showsBinary1 n d x y produces the string -- representation of a binary data constructor with name n and -- arguments x and y, in precedence context d. -- | Deprecated: Use showsBinaryWith to define -- liftShowsPrec showsBinary1 :: (Show1 f, Show1 g, Show a) => String -> Int -> f a -> g a -> ShowS instance Data.Functor.Classes.Show2 (,) instance GHC.Show.Show a => Data.Functor.Classes.Show1 ((,) a) instance Data.Functor.Classes.Show2 Data.Either.Either instance GHC.Show.Show a => Data.Functor.Classes.Show1 (Data.Either.Either a) instance Data.Functor.Classes.Show2 Data.Functor.Const.Const instance GHC.Show.Show a => Data.Functor.Classes.Show1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Read2 (,) instance GHC.Read.Read a => Data.Functor.Classes.Read1 ((,) a) instance Data.Functor.Classes.Read2 Data.Either.Either instance GHC.Read.Read a => Data.Functor.Classes.Read1 (Data.Either.Either a) instance Data.Functor.Classes.Read2 Data.Functor.Const.Const instance GHC.Read.Read a => Data.Functor.Classes.Read1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Ord2 (,) instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 ((,) a) instance Data.Functor.Classes.Ord2 Data.Either.Either instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 (Data.Either.Either a) instance Data.Functor.Classes.Ord2 Data.Functor.Const.Const instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Eq2 (,) instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 ((,) a) instance Data.Functor.Classes.Eq2 Data.Either.Either instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 (Data.Either.Either a) instance Data.Functor.Classes.Eq2 Data.Functor.Const.Const instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 (Data.Functor.Const.Const a) instance Data.Functor.Classes.Show1 GHC.Maybe.Maybe instance Data.Functor.Classes.Show1 [] instance Data.Functor.Classes.Show1 GHC.Base.NonEmpty instance Data.Functor.Classes.Show1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Show1 Data.Proxy.Proxy instance Data.Functor.Classes.Show1 Data.Ord.Down instance Data.Functor.Classes.Read1 GHC.Maybe.Maybe instance Data.Functor.Classes.Read1 [] instance Data.Functor.Classes.Read1 GHC.Base.NonEmpty instance Data.Functor.Classes.Read1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Read1 Data.Proxy.Proxy instance Data.Functor.Classes.Read1 Data.Ord.Down instance Data.Functor.Classes.Ord1 GHC.Maybe.Maybe instance Data.Functor.Classes.Ord1 [] instance Data.Functor.Classes.Ord1 GHC.Base.NonEmpty instance Data.Functor.Classes.Ord1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Ord1 Data.Proxy.Proxy instance Data.Functor.Classes.Ord1 Data.Ord.Down instance Data.Functor.Classes.Eq1 GHC.Maybe.Maybe instance Data.Functor.Classes.Eq1 [] instance Data.Functor.Classes.Eq1 GHC.Base.NonEmpty instance Data.Functor.Classes.Eq1 Data.Functor.Identity.Identity instance Data.Functor.Classes.Eq1 Data.Proxy.Proxy instance Data.Functor.Classes.Eq1 Data.Ord.Down 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. -- -- If you supply bimap, you should ensure that: -- --
-- bimap id id ≡ id ---- -- If you supply first and second, ensure: -- --
-- first id ≡ id -- second id ≡ id ---- -- If you supply both, you should also ensure: -- --
-- bimap f g ≡ first f . second g ---- -- These ensure by parametricity: -- --
-- bimap (f . g) (h . i) ≡ bimap f h . bimap g i -- first (f . g) ≡ first f . first g -- second (f . g) ≡ second f . second g --class Bifunctor p -- | Map over both arguments at the same time. -- --
-- bimap f g ≡ first f . second g ---- --
-- >>> bimap 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 ---- --
-- >>> 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. -- --
-- second ≡ bimap id ---- --
-- >>> 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 (,) instance Data.Bifunctor.Bifunctor ((,,) x1) instance Data.Bifunctor.Bifunctor ((,,,) x1 x2) instance Data.Bifunctor.Bifunctor ((,,,,) x1 x2 x3) instance Data.Bifunctor.Bifunctor ((,,,,,) x1 x2 x3 x4) instance Data.Bifunctor.Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) instance Data.Bifunctor.Bifunctor Data.Either.Either instance Data.Bifunctor.Bifunctor Data.Functor.Const.Const instance Data.Bifunctor.Bifunctor (GHC.Generics.K1 i) module Data.Bifoldable -- | Bifoldable identifies foldable structures with two different -- varieties of elements (as opposed to Foldable, which has one -- variety of element). Common examples are Either and -- (,): -- --
-- instance Bifoldable Either where -- bifoldMap f _ (Left a) = f a -- bifoldMap _ g (Right b) = g b -- -- instance Bifoldable (,) where -- bifoldr f g z (a, b) = f a (g b z) ---- -- 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: -- --
-- bifold ≡ bifoldMap id id -- bifoldMap f g ≡ bifoldr (mappend . f) (mappend . g) mempty -- bifoldr f g z t ≡ appEndo (bifoldMap (Endo . f) (Endo . g) t) z ---- -- If the type is also a Bifunctor instance, it should satisfy: -- --
-- bifoldMap f g ≡ bifold . bimap f g ---- -- which implies that -- --
-- bifoldMap f g . bimap h i ≡ bifoldMap (f . h) (g . i) --class Bifoldable p -- | Combines the elements of a structure using a monoid. -- --
-- bifold ≡ bifoldMap id id ---- --
-- >>> 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 ---- --
-- >>> 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 ---- --
-- > 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. -- --
-- > 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> biList (18, 42) -- [18,42] ---- --
-- >>> biList (Left 18) -- [18] --biList :: Bifoldable t => t a a -> [a] -- | Test whether the structure is empty. -- --
-- >>> 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. -- --
-- >>> 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? -- --
-- >>> 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. -- --
-- >>> 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 :: forall t a. (Bifoldable t, Ord a) => t a a -> a -- | The least element of a non-empty structure. -- --
-- >>> 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 :: forall t a. (Bifoldable t, Ord a) => t a a -> a -- | The bisum function computes the sum of the numbers of a -- structure. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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 (,) instance Data.Bifoldable.Bifoldable Data.Functor.Const.Const instance Data.Bifoldable.Bifoldable (GHC.Generics.K1 i) instance Data.Bifoldable.Bifoldable ((,,) x) instance Data.Bifoldable.Bifoldable ((,,,) x y) instance Data.Bifoldable.Bifoldable ((,,,,) x y z) instance Data.Bifoldable.Bifoldable ((,,,,,) x y z w) instance Data.Bifoldable.Bifoldable ((,,,,,,) x y z w v) instance Data.Bifoldable.Bifoldable Data.Either.Either module Data.Bitraversable -- | Bitraversable identifies bifunctorial data structures whose -- elements can be traversed in order, performing Applicative or -- Monad actions at each element, and collecting a result -- structure with the same shape. -- -- As opposed to Traversable data structures, which have one -- variety of element on which an action can be performed, -- Bitraversable data structures have two such varieties of -- elements. -- -- A definition of bitraverse must satisfy the following laws: -- --
-- 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 -- | Evaluates the relevant functions at each element in the structure, -- running the action, and builds a new structure with the same shape, -- using the results produced from sequencing the actions. -- --
-- bitraverse f g ≡ bisequenceA . bimap f g ---- -- For a version that ignores the results, see bitraverse_. -- --
-- >>> bitraverse 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_. -- --
-- bisequence ≡ bitraverse id id ---- --
-- >>> 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_. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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 :: forall t a b c d. Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d -- | A default definition of bifoldMap in terms of the -- Bitraversable operations. -- --
-- bifoldMapDefault f g ≡ -- getConst . bitraverse (Const . f) (Const . g) --bifoldMapDefault :: forall t m a b. (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m instance Data.Bitraversable.Bitraversable (,) instance Data.Bitraversable.Bitraversable ((,,) x) instance Data.Bitraversable.Bitraversable ((,,,) x y) instance Data.Bitraversable.Bitraversable ((,,,,) x y z) instance Data.Bitraversable.Bitraversable ((,,,,,) x y z w) instance Data.Bitraversable.Bitraversable ((,,,,,,) x y z w v) instance Data.Bitraversable.Bitraversable Data.Either.Either instance Data.Bitraversable.Bitraversable Data.Functor.Const.Const instance Data.Bitraversable.Bitraversable (GHC.Generics.K1 i) -- | This module provides scalable event notification for file descriptors -- and timeouts. -- -- This module should be considered GHC internal. -- --
-- ... mask_ $ forkIOWithUnmask $ \unmask -> -- catch (unmask ...) handler ---- -- so that the exception handler in the child thread is established with -- asynchronous exceptions masked, meanwhile the main body of the child -- thread is executed in the unmasked state. -- -- Note that the unmask function passed to the child thread should only -- be used in that thread; the behaviour is undefined if it is invoked in -- a different thread. forkIOWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | Like forkIO, but lets you specify on which capability the -- thread should run. Unlike a forkIO thread, a thread created by -- forkOn will stay on the same capability for its entire lifetime -- (forkIO threads can migrate between capabilities according to -- the scheduling policy). forkOn is useful for overriding the -- scheduling policy when you know in advance how best to distribute the -- threads. -- -- The Int argument specifies a capability number (see -- getNumCapabilities). Typically capabilities correspond to -- physical processors, but the exact behaviour is -- implementation-dependent. The value passed to forkOn is -- interpreted modulo the total number of capabilities as returned by -- getNumCapabilities. -- -- GHC note: the number of capabilities is specified by the +RTS -- -N option when the program is started. Capabilities can be fixed -- to actual processor cores with +RTS -qa if the underlying -- operating system supports that, although in practice this is usually -- unnecessary (and may actually degrade performance in some cases - -- experimentation is recommended). forkOn :: Int -> IO () -> IO ThreadId -- | Like forkIOWithUnmask, but the child thread is pinned to the -- given CPU, as with forkOn. forkOnWithUnmask :: Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | the value passed to the +RTS -N flag. This is the number of -- Haskell threads that can run truly simultaneously at any given time, -- and is typically set to the number of physical processor cores on the -- machine. -- -- Strictly speaking it is better to use getNumCapabilities, -- because the number of capabilities might vary at runtime. numCapabilities :: Int -- | Returns the number of Haskell threads that can run truly -- simultaneously (on separate physical processors) at any given time. To -- change this value, use setNumCapabilities. getNumCapabilities :: IO Int -- | Set the number of Haskell threads that can run truly simultaneously -- (on separate physical processors) at any given time. The number passed -- to forkOn is interpreted modulo this value. The initial value -- is given by the +RTS -N runtime flag. -- -- This is also the number of threads that will participate in parallel -- garbage collection. It is strongly recommended that the number of -- capabilities is not set larger than the number of physical processor -- cores, and it may often be beneficial to leave one or more cores free -- to avoid contention with other processes in the machine. setNumCapabilities :: Int -> IO () -- | Returns the number of CPUs that the machine has getNumProcessors :: IO Int -- | Returns the number of sparks currently in the local spark pool numSparks :: IO Int childHandler :: SomeException -> IO () -- | Returns the ThreadId of the calling thread (GHC only). myThreadId :: IO ThreadId -- | killThread raises the ThreadKilled exception in the -- given thread (GHC only). -- --
-- killThread tid = throwTo tid ThreadKilled --killThread :: ThreadId -> IO () -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- Exception delivery synchronizes between the source and target thread: -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. Exception delivery is also -- atomic with respect to other exceptions. Atomicity is a useful -- property to have when dealing with race conditions: e.g. if there are -- two threads that can kill each other, it is guaranteed that only one -- of the threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () par :: a -> b -> b infixr 0 `par` pseq :: a -> b -> b infixr 0 `pseq` -- | Internal function used by the RTS to run sparks. runSparks :: IO () -- | The yield action allows (forces, in a co-operative multitasking -- implementation) a context-switch to any other currently runnable -- threads (if any), and is occasionally useful when implementing -- concurrency abstractions. yield :: IO () -- | labelThread stores a string as identifier for this thread if -- you built a RTS with debugging support. This identifier will be used -- in the debugging output to make distinction of different threads -- easier (otherwise you only have the thread state object's address in -- the heap). -- -- Other applications like the graphical Concurrent Haskell Debugger -- (http://www.informatik.uni-kiel.de/~fhu/chd/) may choose to -- overload labelThread for their purposes as well. labelThread :: ThreadId -> String -> IO () -- | Make a weak pointer to a ThreadId. It can be important to do -- this if you want to hold a reference to a ThreadId while still -- allowing the thread to receive the BlockedIndefinitely family -- of exceptions (e.g. BlockedIndefinitelyOnMVar). Holding a -- normal ThreadId reference will prevent the delivery of -- BlockedIndefinitely exceptions because the reference could be -- used as the target of throwTo at any time, which would unblock -- the thread. -- -- Holding a Weak ThreadId, on the other hand, will not prevent -- the thread from receiving BlockedIndefinitely exceptions. It -- is still possible to throw an exception to a Weak ThreadId, -- but the caller must use deRefWeak first to determine whether -- the thread still exists. mkWeakThreadId :: ThreadId -> IO (Weak ThreadId) -- | The current status of a thread data ThreadStatus -- | the thread is currently runnable or running ThreadRunning :: ThreadStatus -- | the thread has finished ThreadFinished :: ThreadStatus -- | the thread is blocked on some resource ThreadBlocked :: BlockReason -> ThreadStatus -- | the thread received an uncaught exception ThreadDied :: ThreadStatus data BlockReason -- | blocked on MVar BlockedOnMVar :: BlockReason -- | blocked on a computation in progress by another thread BlockedOnBlackHole :: BlockReason -- | blocked in throwTo BlockedOnException :: BlockReason -- | blocked in retry in an STM transaction BlockedOnSTM :: BlockReason -- | currently in a foreign call BlockedOnForeignCall :: BlockReason -- | blocked on some other resource. Without -threaded, I/O and -- threadDelay show up as BlockedOnOther, with -- -threaded they show up as BlockedOnMVar. BlockedOnOther :: BlockReason threadStatus :: ThreadId -> IO ThreadStatus -- | Returns the number of the capability on which the thread is currently -- running, and a boolean indicating whether the thread is locked to that -- capability or not. A thread is locked to a capability if it was -- created with forkOn. threadCapability :: ThreadId -> IO (Int, Bool) -- | Make a StablePtr that can be passed to the C function -- hs_try_putmvar(). The RTS wants a StablePtr to the -- underlying MVar#, but a StablePtr# can only refer to -- lifted types, so we have to cheat by coercing. newStablePtrPrimMVar :: MVar () -> IO (StablePtr PrimMVar) data PrimMVar -- | Suspends the current thread for a given number of microseconds (GHC -- only). -- -- There is no guarantee that the thread will be rescheduled promptly -- when the delay has expired, but the thread will never continue to run -- earlier than specified. threadDelay :: Int -> IO () -- | 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. 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: -- --
-- 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. -- --
-- 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 will hopefully be corrected at a later date. data ThreadId -- | Returns the ThreadId of the calling thread (GHC only). myThreadId :: IO ThreadId -- | Creates a new thread to run the IO computation passed as the -- first argument, and returns the ThreadId of the newly created -- thread. -- -- The new thread will be a lightweight, unbound thread. Foreign -- calls made by this thread are not guaranteed to be made by any -- particular OS thread; if you need foreign calls to be made by a -- particular OS thread, then use forkOS instead. -- -- The new thread inherits the masked state of the parent (see -- mask). -- -- The newly created thread has an exception handler that discards the -- exceptions BlockedIndefinitelyOnMVar, -- BlockedIndefinitelyOnSTM, and ThreadKilled, and passes -- all other exceptions to the uncaught exception handler. forkIO :: IO () -> IO ThreadId -- | Fork a thread and call the supplied function when the thread is about -- to terminate, with an exception or a returned value. The function is -- called with asynchronous exceptions masked. -- --
-- forkFinally action and_then = -- mask $ \restore -> -- forkIO $ try (restore action) >>= and_then ---- -- This function is useful for informing the parent when a child -- terminates, for example. forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId -- | Like forkIO, but the child thread is passed a function that can -- be used to unmask asynchronous exceptions. This function is typically -- used in the following way -- --
-- ... mask_ $ forkIOWithUnmask $ \unmask -> -- catch (unmask ...) handler ---- -- so that the exception handler in the child thread is established with -- asynchronous exceptions masked, meanwhile the main body of the child -- thread is executed in the unmasked state. -- -- Note that the unmask function passed to the child thread should only -- be used in that thread; the behaviour is undefined if it is invoked in -- a different thread. forkIOWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | killThread raises the ThreadKilled exception in the -- given thread (GHC only). -- --
-- killThread tid = throwTo tid ThreadKilled --killThread :: ThreadId -> IO () -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- Exception delivery synchronizes between the source and target thread: -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. Exception delivery is also -- atomic with respect to other exceptions. Atomicity is a useful -- property to have when dealing with race conditions: e.g. if there are -- two threads that can kill each other, it is guaranteed that only one -- of the threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () -- | Like forkIO, but lets you specify on which capability the -- thread should run. Unlike a forkIO thread, a thread created by -- forkOn will stay on the same capability for its entire lifetime -- (forkIO threads can migrate between capabilities according to -- the scheduling policy). forkOn is useful for overriding the -- scheduling policy when you know in advance how best to distribute the -- threads. -- -- The Int argument specifies a capability number (see -- getNumCapabilities). Typically capabilities correspond to -- physical processors, but the exact behaviour is -- implementation-dependent. The value passed to forkOn is -- interpreted modulo the total number of capabilities as returned by -- getNumCapabilities. -- -- GHC note: the number of capabilities is specified by the +RTS -- -N option when the program is started. Capabilities can be fixed -- to actual processor cores with +RTS -qa if the underlying -- operating system supports that, although in practice this is usually -- unnecessary (and may actually degrade performance in some cases - -- experimentation is recommended). forkOn :: Int -> IO () -> IO ThreadId -- | Like forkIOWithUnmask, but the child thread is pinned to the -- given CPU, as with forkOn. forkOnWithUnmask :: Int -> ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | Returns the number of Haskell threads that can run truly -- simultaneously (on separate physical processors) at any given time. To -- change this value, use setNumCapabilities. getNumCapabilities :: IO Int -- | Set the number of Haskell threads that can run truly simultaneously -- (on separate physical processors) at any given time. The number passed -- to forkOn is interpreted modulo this value. The initial value -- is given by the +RTS -N runtime flag. -- -- This is also the number of threads that will participate in parallel -- garbage collection. It is strongly recommended that the number of -- capabilities is not set larger than the number of physical processor -- cores, and it may often be beneficial to leave one or more cores free -- to avoid contention with other processes in the machine. setNumCapabilities :: Int -> IO () -- | Returns the number of the capability on which the thread is currently -- running, and a boolean indicating whether the thread is locked to that -- capability or not. A thread is locked to a capability if it was -- created with forkOn. threadCapability :: ThreadId -> IO (Int, Bool) -- | The yield action allows (forces, in a co-operative multitasking -- implementation) a context-switch to any other currently runnable -- threads (if any), and is occasionally useful when implementing -- concurrency abstractions. yield :: IO () -- | Suspends the current thread for a given number of microseconds (GHC -- only). -- -- There is no guarantee that the thread will be rescheduled promptly -- when the delay has expired, but the thread will never continue to run -- earlier than specified. threadDelay :: Int -> IO () -- | Block the current thread until data is available to read on the given -- file descriptor (GHC only). -- -- This will throw an IOError if the file descriptor was closed -- while this thread was blocked. To safely close a file descriptor that -- has been used with threadWaitRead, use closeFdWith. threadWaitRead :: Fd -> IO () -- | Block the current thread until data can be written to the given file -- descriptor (GHC only). -- -- This will throw an IOError if the file descriptor was closed -- while this thread was blocked. To safely close a file descriptor that -- has been used with threadWaitWrite, use closeFdWith. threadWaitWrite :: Fd -> IO () -- | Returns an STM action that can be used to wait for data to read from a -- file descriptor. The second returned value is an IO action that can be -- used to deregister interest in the file descriptor. threadWaitReadSTM :: Fd -> IO (STM (), IO ()) -- | Returns an STM action that can be used to wait until data can be -- written to a file descriptor. The second returned value is an IO -- action that can be used to deregister interest in the file descriptor. threadWaitWriteSTM :: Fd -> IO (STM (), IO ()) -- | True if bound threads are supported. If -- rtsSupportsBoundThreads is False, -- isCurrentThreadBound will always return False and both -- forkOS and runInBoundThread will fail. rtsSupportsBoundThreads :: Bool -- | Like forkIO, this sparks off a new thread to run the IO -- computation passed as the first argument, and returns the -- ThreadId of the newly created thread. -- -- However, forkOS creates a bound thread, which is -- necessary if you need to call foreign (non-Haskell) libraries that -- make use of thread-local state, such as OpenGL (see -- Control.Concurrent#boundthreads). -- -- Using forkOS instead of forkIO makes no difference at -- all to the scheduling behaviour of the Haskell runtime system. It is a -- common misconception that you need to use forkOS instead of -- forkIO to avoid blocking all the Haskell threads when making a -- foreign call; this isn't the case. To allow foreign calls to be made -- without blocking all the Haskell threads (with GHC), it is only -- necessary to use the -threaded option when linking your -- program, and to make sure the foreign import is not marked -- unsafe. forkOS :: IO () -> IO ThreadId -- | Like forkIOWithUnmask, but the child thread is a bound thread, -- as with forkOS. forkOSWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId -- | Returns True if the calling thread is bound, that is, if -- it is safe to use foreign libraries that rely on thread-local state -- from the calling thread. isCurrentThreadBound :: IO Bool -- | Run the IO computation passed as the first argument. If the -- calling thread is not bound, a bound thread is created -- temporarily. runInBoundThread doesn't finish until the -- IO computation finishes. -- -- You can wrap a series of foreign function calls that rely on -- thread-local state with runInBoundThread so that you can use -- them without knowing whether the current thread is bound. runInBoundThread :: IO a -> IO a -- | Run the IO computation passed as the first argument. If the -- calling thread is bound, an unbound thread is created -- temporarily using forkIO. runInBoundThread doesn't -- finish until the IO computation finishes. -- -- Use this function only in the rare case that you have actually -- observed a performance loss due to the use of bound threads. A program -- that doesn't need its main thread to be bound and makes heavy -- use of concurrency (e.g. a web server), might want to wrap its -- main action in runInUnboundThread. -- -- Note that exceptions which are thrown to the current thread are thrown -- in turn to the thread that is executing the given computation. This -- ensures there's always a way of killing the forked thread. runInUnboundThread :: IO a -> IO a -- | Make a weak pointer to a ThreadId. It can be important to do -- this if you want to hold a reference to a ThreadId while still -- allowing the thread to receive the BlockedIndefinitely family -- of exceptions (e.g. BlockedIndefinitelyOnMVar). Holding a -- normal ThreadId reference will prevent the delivery of -- BlockedIndefinitely exceptions because the reference could be -- used as the target of throwTo at any time, which would unblock -- the thread. -- -- Holding a Weak ThreadId, on the other hand, will not prevent -- the thread from receiving BlockedIndefinitely exceptions. It -- is still possible to throw an exception to a Weak ThreadId, -- but the caller must use deRefWeak first to determine whether -- the thread still exists. mkWeakThreadId :: ThreadId -> IO (Weak ThreadId) -- | Attach a timeout event to arbitrary IO computations. module System.Timeout -- | 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. -- --
-- >>> 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.Show.Show System.Timeout.Timeout instance GHC.Exception.Type.Exception System.Timeout.Timeout -- | "Scrap your boilerplate" --- Generic programming in Haskell. See -- http://www.haskell.org/haskellwiki/Research_papers/Generics#Scrap_your_boilerplate.21. -- This module provides the Data class with its primitives for -- generic programming, along with instances for many datatypes. It -- corresponds to a merge between the previous -- Data.Generics.Basics and almost all of -- Data.Generics.Instances. The instances that are not present in -- this module were moved to the Data.Generics.Instances module -- in the syb package. -- -- For more information, please visit the new SYB wiki: -- http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB. module Data.Data -- | The Data class comprehends a fundamental primitive -- gfoldl for folding over constructor applications, say terms. -- This primitive can be instantiated in several ways to map over the -- immediate subterms of a term; see the gmap combinators later -- in this class. Indeed, a generic programmer does not necessarily need -- to use the ingenious gfoldl primitive but rather the intuitive -- gmap combinators. The gfoldl primitive is completed by -- means to query top-level constructors, to turn constructor -- representations into proper terms, and to list all possible datatype -- constructors. This completion allows us to serve generic programming -- scenarios like read, show, equality, term generation. -- -- The combinators gmapT, gmapQ, gmapM, etc are all -- provided with default definitions in terms of gfoldl, leaving -- open the opportunity to provide datatype-specific definitions. (The -- inclusion of the gmap combinators as members of class -- Data allows the programmer or the compiler to derive -- specialised, and maybe more efficient code per datatype. Note: -- gfoldl is more higher-order than the gmap combinators. -- This is subject to ongoing benchmarking experiments. It might turn out -- that the gmap combinators will be moved out of the class -- Data.) -- -- Conceptually, the definition of the gmap combinators in terms -- of the primitive gfoldl requires the identification of the -- gfoldl function arguments. Technically, we also need to -- identify the type constructor c for the construction of the -- result type from the folded term type. -- -- In the definition of gmapQx combinators, we use -- phantom type constructors for the c in the type of -- gfoldl because the result type of a query does not involve the -- (polymorphic) type of the term argument. In the definition of -- gmapQl we simply use the plain constant type constructor -- because gfoldl is left-associative anyway and so it is readily -- suited to fold a left-associative binary operation over the immediate -- subterms. In the definition of gmapQr, extra effort is needed. We use -- a higher-order accumulation trick to mediate between left-associative -- constructor application vs. right-associative binary operation (e.g., -- (:)). When the query is meant to compute a value of type -- r, then the result type 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 :: forall r r'. Data a => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r -- | A generic query with a right-associative binary operator gmapQr :: forall r r'. Data a => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r -- | A generic query that processes the immediate subterms and returns a -- list of results. The list is given in the same order as originally -- specified in the declaration of the data constructors. gmapQ :: Data a => (forall d. Data d => d -> u) -> a -> [u] -- | A generic query that processes one child by index (zero-based) gmapQi :: forall u. Data a => Int -> (forall d. Data d => d -> u) -> a -> u -- | A generic monadic transformation that maps over the immediate subterms -- -- The default definition instantiates the type constructor c in -- the type of gfoldl to the monad datatype constructor, defining -- injection and projection using return and >>=. gmapM :: forall m. (Data a, Monad m) => (forall d. Data d => d -> m d) -> a -> m a -- | Transformation of at least one immediate subterm does not fail gmapMp :: forall m. (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Transformation of one immediate subterm with success gmapMo :: forall m. (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Representation of datatypes. A package of constructor representations -- with names of type and module. data DataType -- | Constructs an algebraic datatype mkDataType :: String -> [Constr] -> DataType -- | Constructs the Int type mkIntType :: String -> DataType -- | Constructs the Float type mkFloatType :: String -> DataType -- | Constructs the Char type mkCharType :: String -> DataType -- | Constructs a non-representation for a non-representable type mkNoRepType :: String -> DataType -- | Gets the type constructor including the module dataTypeName :: DataType -> String -- | Public representation of datatypes data DataRep AlgRep :: [Constr] -> DataRep IntRep :: DataRep FloatRep :: DataRep CharRep :: DataRep NoRep :: DataRep -- | Gets the public presentation of a datatype dataTypeRep :: DataType -> DataRep -- | Look up a constructor by its representation repConstr :: DataType -> ConstrRep -> Constr -- | Test for an algebraic type isAlgType :: DataType -> Bool -- | Gets the constructors of an algebraic datatype dataTypeConstrs :: DataType -> [Constr] -- | Gets the constructor for an index (algebraic datatypes only) indexConstr :: DataType -> ConIndex -> Constr -- | Gets the maximum constructor index of an algebraic datatype maxConstrIndex :: DataType -> ConIndex -- | Test for a non-representable type isNorepType :: DataType -> Bool -- | Representation of constructors. Note that equality on constructors -- with different types may not work -- i.e. the constructors for -- False and Nothing may compare equal. data Constr -- | Unique index for datatype constructors, counting from 1 in the order -- they are given in the program text. type ConIndex = Int -- | Fixity of constructors data Fixity Prefix :: Fixity Infix :: Fixity -- | Constructs a constructor mkConstr :: DataType -> String -> [String] -> Fixity -> Constr mkIntegralConstr :: (Integral a, Show a) => DataType -> a -> Constr mkRealConstr :: (Real a, Show a) => DataType -> a -> Constr -- | Makes a constructor for Char. mkCharConstr :: DataType -> Char -> Constr -- | Gets the datatype of a constructor constrType :: Constr -> DataType -- | Public representation of constructors data ConstrRep AlgConstr :: ConIndex -> ConstrRep IntConstr :: Integer -> ConstrRep FloatConstr :: Rational -> ConstrRep CharConstr :: Char -> ConstrRep -- | Gets the public presentation of constructors constrRep :: Constr -> ConstrRep -- | Gets the field labels of a constructor. The list of labels is returned -- in the same order as they were given in the original constructor -- declaration. constrFields :: Constr -> [String] -- | Gets the fixity of a constructor constrFixity :: Constr -> Fixity -- | Gets the index of a constructor (algebraic datatypes only) constrIndex :: Constr -> ConIndex -- | Gets the string for a constructor showConstr :: Constr -> String -- | Lookup a constructor via a string readConstr :: DataType -> String -> Maybe Constr -- | Gets the unqualified type constructor: drop *.*.*... before name tyconUQname :: String -> String -- | Gets the module of a type constructor: take *.*.*... before name tyconModule :: String -> String -- | Build a term skeleton fromConstr :: Data a => Constr -> a -- | Build a term and use a generic function for subterms fromConstrB :: Data a => (forall d. Data d => d) -> Constr -> a -- | Monadic variation on fromConstrB fromConstrM :: forall m a. (Monad m, Data a) => (forall d. Data d => m d) -> Constr -> m a instance GHC.Show.Show Data.Data.ConstrRep instance GHC.Classes.Eq Data.Data.ConstrRep instance GHC.Show.Show Data.Data.Fixity instance GHC.Classes.Eq Data.Data.Fixity instance GHC.Show.Show Data.Data.DataRep instance GHC.Classes.Eq Data.Data.DataRep instance GHC.Show.Show Data.Data.DataType instance Data.Data.Data GHC.Types.Bool 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 Data.Data.Data a => Data.Data.Data (GHC.Base.NonEmpty a) instance Data.Data.Data a => Data.Data.Data (GHC.Maybe.Maybe a) instance Data.Data.Data GHC.Types.Ordering instance (Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Data.Either.Either a b) instance Data.Data.Data () instance (Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (a, b) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c) => Data.Data.Data (a, b, c) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c, Data.Data.Data d) => Data.Data.Data (a, b, c, d) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c, Data.Data.Data d, Data.Data.Data e) => Data.Data.Data (a, b, c, d, e) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c, Data.Data.Data d, Data.Data.Data e, Data.Data.Data f) => Data.Data.Data (a, b, c, d, e, f) instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c, Data.Data.Data d, Data.Data.Data e, Data.Data.Data f, Data.Data.Data g) => Data.Data.Data (a, b, c, d, e, f, g) instance Data.Data.Data Foreign.Ptr.IntPtr instance Data.Data.Data Foreign.Ptr.WordPtr instance Data.Data.Data t => Data.Data.Data (Data.Proxy.Proxy t) 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 (GHC.Types.Coercible a b, Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Data.Type.Coercion.Coercion a b) instance Data.Data.Data a => Data.Data.Data (Data.Functor.Identity.Identity a) instance forall 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 Data.Version.Version instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Internal.Dual a) instance Data.Data.Data Data.Semigroup.Internal.All instance Data.Data.Data Data.Semigroup.Internal.Any instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Internal.Sum a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Internal.Product a) instance Data.Data.Data a => Data.Data.Data (Data.Monoid.First a) instance Data.Data.Data a => Data.Data.Data (Data.Monoid.Last a) instance (Data.Data.Data (f a), Data.Data.Data a, Data.Typeable.Internal.Typeable f) => Data.Data.Data (Data.Semigroup.Internal.Alt f a) 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 p => Data.Data.Data (GHC.Generics.U1 p) instance Data.Data.Data p => Data.Data.Data (GHC.Generics.Par1 p) instance (Data.Data.Data (f p), Data.Typeable.Internal.Typeable f, Data.Data.Data p) => Data.Data.Data (GHC.Generics.Rec1 f p) instance (Data.Typeable.Internal.Typeable i, Data.Data.Data p, Data.Data.Data c) => Data.Data.Data (GHC.Generics.K1 i c p) instance (Data.Data.Data p, Data.Data.Data (f p), Data.Typeable.Internal.Typeable c, Data.Typeable.Internal.Typeable i, Data.Typeable.Internal.Typeable f) => Data.Data.Data (GHC.Generics.M1 i c f p) instance (Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable g, Data.Data.Data p, Data.Data.Data (f p), Data.Data.Data (g p)) => Data.Data.Data ((GHC.Generics.:+:) f g p) instance (Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable g, Data.Data.Data p, Data.Data.Data (f (g p))) => Data.Data.Data ((GHC.Generics.:.:) f g p) instance Data.Data.Data p => Data.Data.Data (GHC.Generics.V1 p) instance (Data.Typeable.Internal.Typeable f, Data.Typeable.Internal.Typeable g, Data.Data.Data p, Data.Data.Data (f p), Data.Data.Data (g p)) => Data.Data.Data ((GHC.Generics.:*:) f g p) instance Data.Data.Data GHC.Generics.Fixity instance Data.Data.Data GHC.Generics.Associativity instance Data.Data.Data GHC.Generics.SourceUnpackedness instance Data.Data.Data GHC.Generics.SourceStrictness instance Data.Data.Data GHC.Generics.DecidedStrictness instance Data.Data.Data a => Data.Data.Data (Data.Ord.Down a) instance Data.Data.Data GHC.Types.Char instance Data.Data.Data GHC.Types.Float instance Data.Data.Data GHC.Types.Double instance Data.Data.Data GHC.Types.Int instance Data.Data.Data GHC.Integer.Type.Integer instance Data.Data.Data GHC.Natural.Natural instance Data.Data.Data GHC.Int.Int8 instance Data.Data.Data GHC.Int.Int16 instance Data.Data.Data GHC.Int.Int32 instance Data.Data.Data GHC.Int.Int64 instance Data.Data.Data GHC.Types.Word instance Data.Data.Data GHC.Word.Word8 instance Data.Data.Data GHC.Word.Word16 instance Data.Data.Data GHC.Word.Word32 instance Data.Data.Data GHC.Word.Word64 instance (Data.Data.Data a, GHC.Real.Integral a) => Data.Data.Data (GHC.Real.Ratio a) instance Data.Data.Data a => Data.Data.Data [a] instance Data.Data.Data a => Data.Data.Data (GHC.Ptr.Ptr a) instance Data.Data.Data a => Data.Data.Data (GHC.ForeignPtr.ForeignPtr a) instance (Data.Data.Data a, Data.Data.Data b, GHC.Ix.Ix a) => Data.Data.Data (GHC.Arr.Array a b) instance GHC.Show.Show Data.Data.Constr instance GHC.Classes.Eq Data.Data.Constr -- | Support code for desugaring in GHC module GHC.Desugar (>>>) :: forall arr. 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) ---- --
-- >>> (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: -- -- class Semigroup a -- | An associative operation. -- --
-- >>> [1,2,3] <> [4,5,6] -- [1,2,3,4,5,6] --(<>) :: Semigroup a => a -> a -> a -- | Reduce a non-empty list with <> -- -- The default definition should be sufficient, but this can be -- overridden for efficiency. -- --
-- >>> import Data.List.NonEmpty -- -- >>> sconcat $ "Hello" :| [" ", "Haskell", "!"] -- "Hello Haskell!" --sconcat :: Semigroup a => NonEmpty a -> a -- | Repeat a value n times. -- -- Given that this works on a Semigroup it is allowed to fail if -- you request 0 or fewer repetitions, and the default definition will do -- so. -- -- By making this a member of the class, idempotent semigroups and -- monoids can upgrade this to execute in <math> by picking -- stimes = stimesIdempotent or stimes = -- stimesIdempotentMonoid respectively. -- --
-- >>> stimes 4 [1] -- [1,1,1,1] --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 mappend 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 ---- -- Implemented using stimes and mempty. -- -- This is a suitable definition for an mtimes member of -- Monoid. mtimesDefault :: (Integral b, Monoid a) => b -> a -> a newtype Min a Min :: a -> Min a [getMin] :: Min a -> a newtype Max a Max :: a -> Max a [getMax] :: Max a -> a -- | Use Option (First a) to get the behavior of -- First from Data.Monoid. newtype First a First :: a -> First a [getFirst] :: First a -> a -- | Use Option (Last a) to get the behavior of -- Last from Data.Monoid newtype Last a Last :: a -> Last a [getLast] :: Last a -> a -- | Provide a Semigroup for an arbitrary Monoid. -- -- 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 -- mappend. -- --
-- >>> getDual (mappend (Dual "Hello") (Dual "World")) -- "WorldHello" --newtype Dual a Dual :: a -> Dual a [getDual] :: Dual a -> a -- | The monoid of endomorphisms under composition. -- --
-- >>> let computation = Endo ("Hello, " ++) <> Endo (++ "!") -- -- >>> appEndo computation "Haskell" -- "Hello, Haskell!" --newtype Endo a Endo :: (a -> a) -> Endo a [appEndo] :: Endo a -> a -> a -- | Boolean monoid under conjunction (&&). -- --
-- >>> getAll (All True <> mempty <> All False) -- False ---- --
-- >>> getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8])) -- False --newtype All All :: Bool -> All [getAll] :: All -> Bool -- | Boolean monoid under disjunction (||). -- --
-- >>> getAny (Any True <> mempty <> Any False) -- True ---- --
-- >>> getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8])) -- True --newtype Any Any :: Bool -> Any [getAny] :: Any -> Bool -- | Monoid under addition. -- --
-- >>> getSum (Sum 1 <> Sum 2 <> mempty) -- 3 --newtype Sum a Sum :: a -> Sum a [getSum] :: Sum a -> a -- | Monoid under multiplication. -- --
-- >>> getProduct (Product 3 <> Product 4 <> mempty) -- 12 --newtype Product a Product :: a -> Product a [getProduct] :: Product a -> a -- | Option is effectively Maybe with a better instance of -- Monoid, built off of an underlying Semigroup instead of -- an underlying Monoid. -- -- Ideally, this type would not exist at all and we would just fix the -- Monoid instance of Maybe. -- -- In GHC 8.4 and higher, the Monoid instance for Maybe has -- been corrected to lift a Semigroup instance instead of a -- Monoid instance. Consequently, this type is no longer useful. -- It will be marked deprecated in GHC 8.8 and removed in GHC 8.10. newtype Option a Option :: Maybe a -> Option a [getOption] :: Option a -> Maybe a -- | Fold an Option case-wise, just like maybe. option :: b -> (a -> b) -> Option a -> b -- | This lets you use a difference list of a Semigroup as a -- Monoid. -- --
-- >>> 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. 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. -- --
-- >>> minimum [ Arg (x * x) x | x <- [-10 .. 10] ] -- Arg 0 0 --data Arg a b Arg :: a -> b -> Arg a b -- |
-- >>> Min (Arg 0 ()) <> Min (Arg 1 ()) -- Min {getMin = Arg 0 ()} --type ArgMin a b = Min (Arg a b) -- |
-- >>> Max (Arg 0 ()) <> Max (Arg 1 ()) -- Max {getMax = Arg 1 ()} --type ArgMax a b = Max (Arg a b) instance GHC.Generics.Generic1 Data.Semigroup.Min instance GHC.Generics.Generic (Data.Semigroup.Min a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Min a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Min a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Min a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Min a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Min a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.Min a) instance GHC.Generics.Generic1 Data.Semigroup.Max instance GHC.Generics.Generic (Data.Semigroup.Max a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Max a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Max a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Max a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Max a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Max a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.Max a) instance GHC.Generics.Generic1 (Data.Semigroup.Arg a) instance GHC.Generics.Generic (Data.Semigroup.Arg a b) instance (Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Data.Semigroup.Arg a b) instance (GHC.Read.Read a, GHC.Read.Read b) => GHC.Read.Read (Data.Semigroup.Arg a b) instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Data.Semigroup.Arg a b) instance GHC.Generics.Generic1 Data.Semigroup.First instance GHC.Generics.Generic (Data.Semigroup.First a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.First a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.First a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.First a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.First a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.First a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.First a) instance GHC.Generics.Generic1 Data.Semigroup.Last instance GHC.Generics.Generic (Data.Semigroup.Last a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Last a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Last a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Last a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Last a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Last a) instance GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Semigroup.Last a) instance GHC.Generics.Generic1 Data.Semigroup.WrappedMonoid instance GHC.Generics.Generic (Data.Semigroup.WrappedMonoid m) instance Data.Data.Data m => Data.Data.Data (Data.Semigroup.WrappedMonoid m) instance GHC.Read.Read m => GHC.Read.Read (Data.Semigroup.WrappedMonoid m) instance GHC.Show.Show m => GHC.Show.Show (Data.Semigroup.WrappedMonoid m) instance GHC.Classes.Ord m => GHC.Classes.Ord (Data.Semigroup.WrappedMonoid m) instance GHC.Classes.Eq m => GHC.Classes.Eq (Data.Semigroup.WrappedMonoid m) instance GHC.Enum.Bounded m => GHC.Enum.Bounded (Data.Semigroup.WrappedMonoid m) instance GHC.Generics.Generic1 Data.Semigroup.Option instance GHC.Generics.Generic (Data.Semigroup.Option a) instance Data.Data.Data a => Data.Data.Data (Data.Semigroup.Option a) instance GHC.Read.Read a => GHC.Read.Read (Data.Semigroup.Option a) instance GHC.Show.Show a => GHC.Show.Show (Data.Semigroup.Option a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Option a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Option a) instance GHC.Base.Functor Data.Semigroup.Option instance GHC.Base.Applicative Data.Semigroup.Option instance GHC.Base.Monad Data.Semigroup.Option instance GHC.Base.Alternative Data.Semigroup.Option instance GHC.Base.MonadPlus Data.Semigroup.Option instance Control.Monad.Fix.MonadFix Data.Semigroup.Option instance Data.Foldable.Foldable Data.Semigroup.Option instance Data.Traversable.Traversable Data.Semigroup.Option instance GHC.Base.Semigroup a => GHC.Base.Semigroup (Data.Semigroup.Option a) instance GHC.Base.Semigroup a => GHC.Base.Monoid (Data.Semigroup.Option a) instance GHC.Base.Monoid m => GHC.Base.Semigroup (Data.Semigroup.WrappedMonoid m) instance GHC.Base.Monoid m => GHC.Base.Monoid (Data.Semigroup.WrappedMonoid m) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.WrappedMonoid a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.Last a) instance GHC.Base.Semigroup (Data.Semigroup.Last a) instance GHC.Base.Functor Data.Semigroup.Last instance Data.Foldable.Foldable Data.Semigroup.Last instance Data.Traversable.Traversable Data.Semigroup.Last instance GHC.Base.Applicative Data.Semigroup.Last instance GHC.Base.Monad Data.Semigroup.Last instance Control.Monad.Fix.MonadFix Data.Semigroup.Last instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.First a) instance GHC.Base.Semigroup (Data.Semigroup.First a) instance GHC.Base.Functor Data.Semigroup.First instance Data.Foldable.Foldable Data.Semigroup.First instance Data.Traversable.Traversable Data.Semigroup.First instance GHC.Base.Applicative Data.Semigroup.First instance GHC.Base.Monad Data.Semigroup.First instance Control.Monad.Fix.MonadFix Data.Semigroup.First instance GHC.Base.Functor (Data.Semigroup.Arg a) instance Data.Foldable.Foldable (Data.Semigroup.Arg a) instance Data.Traversable.Traversable (Data.Semigroup.Arg a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Semigroup.Arg a b) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Semigroup.Arg a b) instance Data.Bifunctor.Bifunctor Data.Semigroup.Arg instance Data.Bifoldable.Bifoldable Data.Semigroup.Arg instance Data.Bitraversable.Bitraversable Data.Semigroup.Arg instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.Max a) instance GHC.Classes.Ord a => GHC.Base.Semigroup (Data.Semigroup.Max a) instance (GHC.Classes.Ord a, GHC.Enum.Bounded a) => GHC.Base.Monoid (Data.Semigroup.Max a) instance GHC.Base.Functor Data.Semigroup.Max instance Data.Foldable.Foldable Data.Semigroup.Max instance Data.Traversable.Traversable Data.Semigroup.Max instance GHC.Base.Applicative Data.Semigroup.Max instance GHC.Base.Monad Data.Semigroup.Max instance Control.Monad.Fix.MonadFix Data.Semigroup.Max instance GHC.Num.Num a => GHC.Num.Num (Data.Semigroup.Max a) instance GHC.Enum.Enum a => GHC.Enum.Enum (Data.Semigroup.Min a) instance GHC.Classes.Ord a => GHC.Base.Semigroup (Data.Semigroup.Min a) instance (GHC.Classes.Ord a, GHC.Enum.Bounded a) => GHC.Base.Monoid (Data.Semigroup.Min a) instance GHC.Base.Functor Data.Semigroup.Min instance Data.Foldable.Foldable Data.Semigroup.Min instance Data.Traversable.Traversable Data.Semigroup.Min instance GHC.Base.Applicative Data.Semigroup.Min instance GHC.Base.Monad Data.Semigroup.Min instance Control.Monad.Fix.MonadFix Data.Semigroup.Min instance GHC.Num.Num a => GHC.Num.Num (Data.Semigroup.Min a) -- | 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. -- -- Using ApplicativeDo: 'vacuous theVoid' can be -- understood as the do expression -- --
-- do void <- theVoid -- pure (absurd void) ---- -- with an inferred Functor constraint. vacuous :: Functor f => f Void -> f a instance GHC.Show.Show Data.Void.Void instance GHC.Read.Read Data.Void.Void instance GHC.Classes.Ord Data.Void.Void instance GHC.Generics.Generic Data.Void.Void instance Data.Data.Data Data.Void.Void instance GHC.Classes.Eq Data.Void.Void instance GHC.Ix.Ix Data.Void.Void instance GHC.Exception.Type.Exception Data.Void.Void instance GHC.Base.Semigroup Data.Void.Void -- | Sums, lifted to functors. module Data.Functor.Sum -- | Lifted sum of functors. data Sum f g a InL :: f a -> Sum f g a InR :: g a -> Sum f g a instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (Data.Functor.Sum.Sum f g) instance forall k (f :: k -> *) (g :: k -> *) (a :: k). GHC.Generics.Generic (Data.Functor.Sum.Sum f g a) instance forall k (f :: k -> *) (g :: k -> *) (a :: k). (Data.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 (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g) => Data.Functor.Classes.Ord1 (Data.Functor.Sum.Sum f g) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g) => Data.Functor.Classes.Read1 (Data.Functor.Sum.Sum f g) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g) => Data.Functor.Classes.Show1 (Data.Functor.Sum.Sum f g) instance (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g, GHC.Classes.Eq a) => GHC.Classes.Eq (Data.Functor.Sum.Sum f g a) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g, GHC.Classes.Ord a) => GHC.Classes.Ord (Data.Functor.Sum.Sum f g a) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g, GHC.Read.Read a) => GHC.Read.Read (Data.Functor.Sum.Sum f g a) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g, GHC.Show.Show a) => GHC.Show.Show (Data.Functor.Sum.Sum f g a) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (Data.Functor.Sum.Sum f g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (Data.Functor.Sum.Sum f g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (Data.Functor.Sum.Sum f g) -- | Products, lifted to functors. module Data.Functor.Product -- | Lifted product of functors. data Product f g a Pair :: f a -> g a -> Product f g a instance forall k (f :: k -> *) (g :: k -> *). GHC.Generics.Generic1 (Data.Functor.Product.Product f g) instance forall k (f :: k -> *) (g :: k -> *) (a :: k). GHC.Generics.Generic (Data.Functor.Product.Product f g a) instance forall k (f :: k -> *) (g :: k -> *) (a :: k). (Data.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 (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g) => Data.Functor.Classes.Ord1 (Data.Functor.Product.Product f g) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g) => Data.Functor.Classes.Read1 (Data.Functor.Product.Product f g) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g) => Data.Functor.Classes.Show1 (Data.Functor.Product.Product f g) instance (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g, GHC.Classes.Eq a) => GHC.Classes.Eq (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g, GHC.Classes.Ord a) => GHC.Classes.Ord (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g, GHC.Read.Read a) => GHC.Read.Read (Data.Functor.Product.Product f g a) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g, GHC.Show.Show a) => GHC.Show.Show (Data.Functor.Product.Product f g a) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (Data.Functor.Product.Product f g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (Data.Functor.Product.Product f g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (Data.Functor.Product.Product f g) instance (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (Data.Functor.Product.Product f g) instance (GHC.Base.Alternative f, GHC.Base.Alternative g) => GHC.Base.Alternative (Data.Functor.Product.Product f g) instance (GHC.Base.Monad f, GHC.Base.Monad g) => GHC.Base.Monad (Data.Functor.Product.Product f g) instance (GHC.Base.MonadPlus f, GHC.Base.MonadPlus g) => GHC.Base.MonadPlus (Data.Functor.Product.Product f g) instance (Control.Monad.Fix.MonadFix f, Control.Monad.Fix.MonadFix g) => Control.Monad.Fix.MonadFix (Data.Functor.Product.Product f g) instance (Control.Monad.Zip.MonadZip f, Control.Monad.Zip.MonadZip g) => Control.Monad.Zip.MonadZip (Data.Functor.Product.Product f g) -- | Composition of functors. module Data.Functor.Compose -- | Right-to-left composition of functors. The composition of applicative -- functors is always applicative, but the composition of monads is not -- always a monad. newtype Compose f g a Compose :: f (g a) -> Compose f g a [getCompose] :: Compose f g a -> f (g a) infixr 9 `Compose` infixr 9 `Compose` instance forall (f :: * -> *) k (g :: k -> *). GHC.Base.Functor f => GHC.Generics.Generic1 (Data.Functor.Compose.Compose f g) instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). GHC.Generics.Generic (Data.Functor.Compose.Compose f g a) instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). (Data.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 (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g) => Data.Functor.Classes.Eq1 (Data.Functor.Compose.Compose f g) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g) => Data.Functor.Classes.Ord1 (Data.Functor.Compose.Compose f g) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g) => Data.Functor.Classes.Read1 (Data.Functor.Compose.Compose f g) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g) => Data.Functor.Classes.Show1 (Data.Functor.Compose.Compose f g) instance (Data.Functor.Classes.Eq1 f, Data.Functor.Classes.Eq1 g, GHC.Classes.Eq a) => GHC.Classes.Eq (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Ord1 f, Data.Functor.Classes.Ord1 g, GHC.Classes.Ord a) => GHC.Classes.Ord (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Read1 f, Data.Functor.Classes.Read1 g, GHC.Read.Read a) => GHC.Read.Read (Data.Functor.Compose.Compose f g a) instance (Data.Functor.Classes.Show1 f, Data.Functor.Classes.Show1 g, GHC.Show.Show a) => GHC.Show.Show (Data.Functor.Compose.Compose f g a) instance (GHC.Base.Functor f, GHC.Base.Functor g) => GHC.Base.Functor (Data.Functor.Compose.Compose f g) instance (Data.Foldable.Foldable f, Data.Foldable.Foldable g) => Data.Foldable.Foldable (Data.Functor.Compose.Compose f g) instance (Data.Traversable.Traversable f, Data.Traversable.Traversable g) => Data.Traversable.Traversable (Data.Functor.Compose.Compose f g) instance (GHC.Base.Applicative f, GHC.Base.Applicative g) => GHC.Base.Applicative (Data.Functor.Compose.Compose f g) instance (GHC.Base.Alternative f, GHC.Base.Applicative g) => GHC.Base.Alternative (Data.Functor.Compose.Compose f g) instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1). Data.Type.Equality.TestEquality f => Data.Type.Equality.TestEquality (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 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: -- --