Copyright | (c) The University of Glasgow 2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | [email protected] |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
RealWorld
state transformersGHC Extensions: this is the Approved Way to get at GHC-specific extensions.
Note: no other base module should import this module.
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.
Bounded Int | Since: 2.1 |
Enum Int | Since: 2.1 |
Eq Int | |
Integral Int | Since: 2.0.1 |
Data Int | Since: 4.0.0.0 |
Num Int | Since: 2.1 |
Ord Int | |
Read Int | Since: 2.1 |
Real Int | Since: 2.0.1 |
Show Int | Since: 2.1 |
Ix Int | Since: 2.1 |
FiniteBits Int | Since: 4.6.0.0 |
Bits Int | Since: 2.1 |
Storable Int | Since: 2.1 |
PrintfArg Int | Since: 2.1 |
Generic1 k (URec k Int) | |
Functor (URec * Int) | |
Foldable (URec * Int) | |
Traversable (URec * Int) | |
Eq (URec k Int p) | |
Ord (URec k Int p) | |
Show (URec k Int p) | |
Generic (URec k Int p) | |
data URec k Int |
Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 k (URec k Int) | |
type Rep (URec k Int p) | |
A Word
is an unsigned integral type, with the same size as Int
.
Bounded Word | Since: 2.1 |
Enum Word | Since: 2.1 |
Eq Word | |
Integral Word | Since: 2.1 |
Data Word | Since: 4.0.0.0 |
Num Word | Since: 2.1 |
Ord Word | |
Read Word | Since: 4.5.0.0 |
Real Word | Since: 2.1 |
Show Word | Since: 2.1 |
Ix Word | Since: 4.6.0.0 |
FiniteBits Word | Since: 4.6.0.0 |
Bits Word | Since: 2.1 |
Storable Word | Since: 2.1 |
PrintfArg Word | Since: 2.1 |
Generic1 k (URec k Word) | |
Functor (URec * Word) | |
Foldable (URec * Word) | |
Traversable (URec * Word) | |
Eq (URec k Word p) | |
Ord (URec k Word p) | |
Show (URec k Word p) | |
Generic (URec k Word p) | |
data URec k Word |
Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 k (URec k Word) | |
type Rep (URec k Word p) | |
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.
Eq Float | |
Floating Float | Since: 2.1 |
Data Float | Since: 4.0.0.0 |
Ord Float | |
Read Float | Since: 2.1 |
RealFloat Float | Since: 2.1 |
Storable Float | Since: 2.1 |
PrintfArg Float | Since: 2.1 |
Generic1 k (URec k Float) | |
Functor (URec * Float) | |
Foldable (URec * Float) | |
Traversable (URec * Float) | |
Eq (URec k Float p) | |
Ord (URec k Float p) | |
Show (URec k Float p) | |
Generic (URec k Float p) | |
data URec k Float |
Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 k (URec k Float) | |
type Rep (URec k Float p) | |
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.
Eq Double | |
Floating Double | Since: 2.1 |
Data Double | Since: 4.0.0.0 |
Ord Double | |
Read Double | Since: 2.1 |
RealFloat Double | Since: 2.1 |
Storable Double | Since: 2.1 |
PrintfArg Double | Since: 2.1 |
Generic1 k (URec k Double) | |
Functor (URec * Double) | |
Foldable (URec * Double) | |
Traversable (URec * Double) | |
Eq (URec k Double p) | |
Ord (URec k Double p) | |
Show (URec k Double p) | |
Generic (URec k Double p) | |
data URec k Double |
Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 k (URec k Double) | |
type Rep (URec k Double p) | |
The character type Char
is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) characters (see http://www.unicode.org/ for details). This set extends the ISO 8859-1 (Latin-1) character set (the first 256 characters), which is itself an extension of the ASCII character set (the first 128 characters). A character literal in Haskell has type Char
.
To convert a Char
to or from the corresponding Int
value defined by Unicode, use toEnum
and fromEnum
from the Enum
class respectively (or equivalently ord
and chr
).
Bounded Char | Since: 2.1 |
Enum Char | Since: 2.1 |
Eq Char | |
Data Char | Since: 4.0.0.0 |
Ord Char | |
Read Char | Since: 2.1 |
Show Char | Since: 2.1 |
Ix Char | Since: 2.1 |
Storable Char | Since: 2.1 |
IsChar Char | Since: 2.1 |
PrintfArg Char | Since: 2.1 |
Generic1 k (URec k Char) | |
Functor (URec * Char) | |
Foldable (URec * Char) | |
Traversable (URec * Char) | |
Eq (URec k Char p) | |
Ord (URec k Char p) | |
Show (URec k Char p) | |
Generic (URec k Char p) | |
data URec k Char |
Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 k (URec k Char) | |
type Rep (URec k Char p) | |
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
.
Generic1 k (URec k (Ptr ())) | |
Eq (Ptr a) | |
Data a => Data (Ptr a) | Since: 4.8.0.0 |
Ord (Ptr a) | |
Show (Ptr a) | Since: 2.1 |
Storable (Ptr a) | Since: 2.1 |
Functor (URec * (Ptr ())) | |
Foldable (URec * (Ptr ())) | |
Traversable (URec * (Ptr ())) | |
Eq (URec k (Ptr ()) p) | |
Ord (URec k (Ptr ()) p) | |
Generic (URec k (Ptr ()) p) | |
data URec k (Ptr ()) |
Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 k (URec k (Ptr ())) | |
type Rep (URec k (Ptr ()) p) | |
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
Char
, Int
, Double
, Float
, Bool
, Int8
, Int16
, Int32
, Int64
, Word8
, Word16
, Word32
, Word64
, Ptr a
, FunPtr a
, StablePtr a
or a renaming of any of these using newtype
.IO t
where t
is a marshallable foreign type or ()
.A value of type FunPtr a
may be a pointer to a foreign function, either returned by another foreign function or imported with a a static address import like
foreign import ccall "stdlib.h &free" p_free :: FunPtr (Ptr a -> IO ())
or a pointer to a Haskell function created using a wrapper stub declared to produce a FunPtr
of the correct type. For example:
type Compare = Int -> Int -> Bool foreign import ccall "wrapper" mkCompare :: Compare -> IO (FunPtr Compare)
Calls to wrapper stubs like mkCompare
allocate storage, which should be released with freeHaskellFunPtr
when no longer required.
To convert FunPtr
values to corresponding Haskell functions, one can define a dynamic stub for the specific foreign type, e.g.
type IntFunction = CInt -> IO () foreign import ccall "dynamic" mkFun :: FunPtr IntFunction -> IntFunction
module GHC.Prim
shiftL# :: Word# -> Int# -> Word# Source
Shift the argument left by the specified number of bits (which must be non-negative).
shiftRL# :: Word# -> Int# -> Word# Source
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#)
iShiftL# :: Int# -> Int# -> Int# Source
Shift the argument left by the specified number of bits (which must be non-negative).
iShiftRA# :: Int# -> Int# -> Int# Source
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)
iShiftRL# :: Int# -> Int# -> Int# Source
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)
uncheckedShiftL64# :: Word# -> Int# -> Word# Source
uncheckedShiftRL64# :: Word# -> Int# -> Word# Source
uncheckedIShiftL64# :: Int# -> Int# -> Int# Source
uncheckedIShiftRA64# :: Int# -> Int# -> Int# Source
isTrue# :: Int# -> Bool Source
Alias for tagToEnum#
. Returns True if its parameter is 1# and False if it is 0#.
build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] Source
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.
augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] Source
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.
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
fromString :: String -> a Source
breakpoint :: a -> a Source
breakpointCond :: Bool -> a -> a Source
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.
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.
oneShot :: (a -> b) -> a -> b Source
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.
runRW# :: (State# RealWorld -> a) -> a Source
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.
These are available from the Trustworthy module Data.Coerce as well
Since: 4.7.0.0
coerce :: Coercible * a b => a -> b Source
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.
class (~R#) k0 k0 a b => Coercible k0 (a :: k0) (b :: k0) Source
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.
Since: 4.7.0.0
class (~#) k0 k1 a b => (k0 ~~ k1) (a :: k0) (b :: k1) Source
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.
data TYPE (a :: RuntimeRep) :: RuntimeRep -> * Source
Functor f => Generic1 k ((:.:) * k f g) | |
Functor f => Generic1 k (Compose * k f g) | |
Monad (U1 *) | Since: 4.9.0.0 |
Monad (Proxy *) | Since: 4.7.0.0 |
Functor (V1 *) | |
Functor (U1 *) | Since: 4.9.0.0 |
Functor (Proxy *) | Since: 4.7.0.0 |
Applicative (U1 *) | Since: 4.9.0.0 |
Applicative (Proxy *) | Since: 4.7.0.0 |
Foldable (V1 *) | |
Foldable (U1 *) | Since: 4.9.0.0 |
Foldable (Proxy *) | Since: 4.7.0.0 |
Traversable (V1 *) | |
Traversable (U1 *) | Since: 4.9.0.0 |
Traversable (Proxy *) | Since: 4.7.0.0 |
MonadPlus (U1 *) | Since: 4.9.0.0 |
MonadPlus (Proxy *) | Since: 4.9.0.0 |
Alternative (U1 *) | Since: 4.9.0.0 |
Alternative (Proxy *) | Since: 4.9.0.0 |
MonadZip (U1 *) | Since: 4.9.0.0 |
MonadZip (Proxy *) | Since: 4.9.0.0 |
Show2 (Const *) | Since: 4.9.0.0 |
Read2 (Const *) | Since: 4.9.0.0 |
Ord2 (Const *) | Since: 4.9.0.0 |
Eq2 (Const *) | Since: 4.9.0.0 |
Show1 (Proxy *) | Since: 4.9.0.0 |
Read1 (Proxy *) | Since: 4.9.0.0 |
Ord1 (Proxy *) | Since: 4.9.0.0 |
Eq1 (Proxy *) | Since: 4.9.0.0 |
Bifunctor (Const *) | Since: 4.8.0.0 |
Bifoldable (Const *) | Since: 4.10.0.0 |
Bitraversable (Const *) | Since: 4.10.0.0 |
Generic1 * [] | |
Generic1 * Maybe | |
Generic1 * Par1 | |
Generic1 * Last | |
Generic1 * First | |
Generic1 * Product | |
Generic1 * Sum | |
Generic1 * Dual | |
Generic1 * Identity | |
Generic1 * ZipList | |
Generic1 * NonEmpty | |
Generic1 * Option | |
Generic1 * WrappedMonoid | |
Generic1 * Last | |
Generic1 * First | |
Generic1 * Max | |
Generic1 * Min | |
Generic1 * Complex | |
Generic1 * (Either a) | |
Generic1 * ((,) a) | |
Generic1 * (WrappedMonad m) | |
Generic1 * (Arg a) | |
Monad m => Category * (Kleisli m) | Since: 3.0 |
Generic1 * ((,,) a b) | |
Generic1 * (WrappedArrow a b) | |
Category * ((->) LiftedRep LiftedRep) | Since: 3.0 |
Generic1 * ((,,,) a b c) | |
Generic1 * ((,,,,) a b c d) | |
Generic1 * ((,,,,,) a b c d e) | |
Generic1 * ((,,,,,,) a b c d e f) | |
Monad f => Monad (Rec1 * f) | Since: 4.9.0.0 |
Monad f => Monad (Alt * f) | |
Data p => Data (V1 * p) | Since: 4.9.0.0 |
Data p => Data (U1 * p) | Since: 4.9.0.0 |
Data t => Data (Proxy * t) | Since: 4.7.0.0 |
Functor f => Functor (Rec1 * f) | |
Functor (URec * Char) | |
Functor (URec * Double) | |
Functor (URec * Float) | |
Functor (URec * Int) | |
Functor (URec * Word) | |
Functor (URec * (Ptr ())) | |
Functor f => Functor (Alt * f) | |
Functor (Const * m) | Since: 2.1 |
MonadFix f => MonadFix (Rec1 * f) | Since: 4.9.0.0 |
MonadFix f => MonadFix (Alt * f) | Since: 4.8.0.0 |
Applicative f => Applicative (Rec1 * f) | Since: 4.9.0.0 |
Applicative f => Applicative (Alt * f) | |
Monoid m => Applicative (Const * m) | Since: 2.0.1 |
Foldable f => Foldable (Rec1 * f) | |
Foldable (URec * Char) | |
Foldable (URec * Double) | |
Foldable (URec * Float) | |
Foldable (URec * Int) | |
Foldable (URec * Word) | |
Foldable (URec * (Ptr ())) | |
Foldable (Const * m) | Since: 4.7.0.0 |
Traversable f => Traversable (Rec1 * f) | |
Traversable (URec * Char) | |
Traversable (URec * Double) | |
Traversable (URec * Float) | |
Traversable (URec * Int) | |
Traversable (URec * Word) | |
Traversable (URec * (Ptr ())) | |
Traversable (Const * m) | Since: 4.7.0.0 |
MonadPlus f => MonadPlus (Rec1 * f) | Since: 4.9.0.0 |
MonadPlus f => MonadPlus (Alt * f) | |
Alternative f => Alternative (Rec1 * f) | Since: 4.9.0.0 |
Alternative f => Alternative (Alt * f) | |
MonadZip f => MonadZip (Rec1 * f) | Since: 4.9.0.0 |
MonadZip f => MonadZip (Alt * f) | Since: 4.8.0.0 |
Show a => Show1 (Const * a) | Since: 4.9.0.0 |
Read a => Read1 (Const * a) | Since: 4.9.0.0 |
Ord a => Ord1 (Const * a) | Since: 4.9.0.0 |
Eq a => Eq1 (Const * a) | Since: 4.9.0.0 |
Bifunctor (K1 * i) | Since: 4.9.0.0 |
Bifoldable (K1 * i) | Since: 4.10.0.0 |
Bitraversable (K1 * i) | Since: 4.10.0.0 |
(Monad f, Monad g) => Monad ((:*:) * f g) | Since: 4.9.0.0 |
(Monad f, Monad g) => Monad (Product * f g) | Since: 4.9.0.0 |
(Data (f p), Typeable (* -> *) f, Data p) => Data (Rec1 * f p) | Since: 4.9.0.0 |
((~) * a b, Data a) => Data ((:~:) * a b) | Since: 4.7.0.0 |
(Coercible * a b, Data a, Data b) => Data (Coercion * a b) | Since: 4.7.0.0 |
(Data (f a), Data a, Typeable (* -> *) f) => Data (Alt * f a) | Since: 4.8.0.0 |
Functor (K1 * i c) | |
(Functor g, Functor f) => Functor ((:+:) * f g) | |
(Functor g, Functor f) => Functor ((:*:) * f g) | |
(Functor f, Functor g) => Functor (Sum * f g) | Since: 4.9.0.0 |
(Functor f, Functor g) => Functor (Product * f g) | Since: 4.9.0.0 |
(MonadFix f, MonadFix g) => MonadFix ((:*:) * f g) | Since: 4.9.0.0 |
(MonadFix f, MonadFix g) => MonadFix (Product * f g) | Since: 4.9.0.0 |
IsString a => IsString (Const * a b) | Since: 4.9.0.0 |
(Applicative f, Applicative g) => Applicative ((:*:) * f g) | Since: 4.9.0.0 |
(Applicative f, Applicative g) => Applicative (Product * f g) | Since: 4.9.0.0 |
Foldable (K1 * i c) | |
(Foldable f, Foldable g) => Foldable ((:+:) * f g) | |
(Foldable f, Foldable g) => Foldable ((:*:) * f g) | |
(Foldable f, Foldable g) => Foldable (Sum * f g) | Since: 4.9.0.0 |
(Foldable f, Foldable g) => Foldable (Product * f g) | Since: 4.9.0.0 |
Traversable (K1 * i c) | |
(Traversable f, Traversable g) => Traversable ((:+:) * f g) | |
(Traversable f, Traversable g) => Traversable ((:*:) * f g) | |
(Traversable f, Traversable g) => Traversable (Sum * f g) | Since: 4.9.0.0 |
(Traversable f, Traversable g) => Traversable (Product * f g) | Since: 4.9.0.0 |
Alternative f => Semigroup (Alt * f a) | Since: 4.9.0.0 |
Alternative f => Monoid (Alt * f a) | Since: 4.8.0.0 |
(MonadPlus f, MonadPlus g) => MonadPlus ((:*:) * f g) | Since: 4.9.0.0 |
(MonadPlus f, MonadPlus g) => MonadPlus (Product * f g) | Since: 4.9.0.0 |
(Alternative f, Alternative g) => Alternative ((:*:) * f g) | Since: 4.9.0.0 |
(Alternative f, Alternative g) => Alternative (Product * f g) | Since: 4.9.0.0 |
(MonadZip f, MonadZip g) => MonadZip ((:*:) * f g) | Since: 4.9.0.0 |
(MonadZip f, MonadZip g) => MonadZip (Product * f g) | Since: 4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Sum * f g) | Since: 4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Product * f g) | Since: 4.9.0.0 |
(Read1 f, Read1 g) => Read1 (Sum * f g) | Since: 4.9.0.0 |
(Read1 f, Read1 g) => Read1 (Product * f g) | Since: 4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Sum * f g) | Since: 4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Product * f g) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Sum * f g) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Product * f g) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Sum * f g a) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Product * f g a) | Since: 4.9.0.0 |
Monad f => Monad (M1 * i c f) | Since: 4.9.0.0 |
(Typeable * i, Data p, Data c) => Data (K1 * i c p) | Since: 4.9.0.0 |
(Typeable (* -> *) f, Typeable (* -> *) g, Data p, Data (f p), Data (g p)) => Data ((:+:) * f g p) | Since: 4.9.0.0 |
(Typeable (* -> *) f, Typeable (* -> *) g, Data p, Data (f p), Data (g p)) => Data ((:*:) * f g p) | Since: 4.9.0.0 |
Functor f => Functor (M1 * i c f) | |
(Functor g, Functor f) => Functor ((:.:) * * f g) | |
(Functor f, Functor g) => Functor (Compose * * f g) | Since: 4.9.0.0 |
(Ord1 f, Ord1 g, Ord a) => Ord (Sum * f g a) | Since: 4.9.0.0 |
(Ord1 f, Ord1 g, Ord a) => Ord (Product * f g a) | Since: 4.9.0.0 |
(Read1 f, Read1 g, Read a) => Read (Sum * f g a) | Since: 4.9.0.0 |
(Read1 f, Read1 g, Read a) => Read (Product * f g a) | Since: 4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Sum * f g a) | Since: 4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Product * f g a) | Since: 4.9.0.0 |
MonadFix f => MonadFix (M1 * i c f) | Since: 4.9.0.0 |
Applicative f => Applicative (M1 * i c f) | Since: 4.9.0.0 |
(Applicative f, Applicative g) => Applicative ((:.:) * * f g) | Since: 4.9.0.0 |
(Applicative f, Applicative g) => Applicative (Compose * * f g) | Since: 4.9.0.0 |
Foldable f => Foldable (M1 * i c f) | |
(Foldable f, Foldable g) => Foldable ((:.:) * * f g) | |
(Foldable f, Foldable g) => Foldable (Compose * * f g) | Since: 4.9.0.0 |
Traversable f => Traversable (M1 * i c f) | |
(Traversable f, Traversable g) => Traversable ((:.:) * * f g) | |
(Traversable f, Traversable g) => Traversable (Compose * * f g) | Since: 4.9.0.0 |
MonadPlus f => MonadPlus (M1 * i c f) | Since: 4.9.0.0 |
Alternative f => Alternative (M1 * i c f) | Since: 4.9.0.0 |
(Alternative f, Applicative g) => Alternative ((:.:) * * f g) | Since: 4.9.0.0 |
(Alternative f, Applicative g) => Alternative (Compose * * f g) | Since: 4.9.0.0 |
MonadZip f => MonadZip (M1 * i c f) | Since: 4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Compose * * f g) | Since: 4.9.0.0 |
(Read1 f, Read1 g) => Read1 (Compose * * f g) | Since: 4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Compose * * f g) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Compose * * f g) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Compose * * f g a) | Since: 4.9.0.0 |
(Data p, Data (f p), Typeable Meta c, Typeable * i, Typeable (* -> *) f) => Data (M1 * i c f p) | Since: 4.9.0.0 |
(Typeable (* -> *) f, Typeable (* -> *) g, Data p, Data (f (g p))) => Data ((:.:) * * f g p) | Since: 4.9.0.0 |
(Ord1 f, Ord1 g, Ord a) => Ord (Compose * * f g a) | Since: 4.9.0.0 |
(Read1 f, Read1 g, Read a) => Read (Compose * * f g a) | Since: 4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Compose * * f g a) | Since: 4.9.0.0 |
type (==) * a b | |
type Rep1 k ((:.:) * k f g) | |
type Rep1 k (Compose * k f g) | |
type Rep1 * [] | |
type Rep1 * Maybe | |
type Rep1 * Par1 | |
type Rep1 * Last | |
type Rep1 * First | |
type Rep1 * Product | |
type Rep1 * Sum | |
type Rep1 * Dual | |
type Rep1 * Identity | |
type Rep1 * ZipList | |
type Rep1 * NonEmpty | |
type Rep1 * Option | |
type Rep1 * WrappedMonoid | |
type Rep1 * Last | |
type Rep1 * First | |
type Rep1 * Max | |
type Rep1 * Min | |
type Rep1 * Complex | |
type Rep1 * (Either a) | |
type Rep1 * ((,) a) | |
type Rep1 * (WrappedMonad m) | |
type Rep1 * (Arg a) | |
type Rep1 * ((,,) a b) | |
type Rep1 * (WrappedArrow a b) | |
type Rep1 * ((,,,) a b c) | |
type Rep1 * ((,,,,) a b c d) | |
type Rep1 * ((,,,,,) a b c d e) | |
type Rep1 * ((,,,,,,) a b c d e f) | |
data RuntimeRep :: * Source
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).
VecRep VecCount VecElem | a SIMD vector type |
TupleRep [RuntimeRep] | An unboxed tuple of the given reps |
SumRep [RuntimeRep] | An unboxed sum of the given reps |
LiftedRep | lifted; represented by a pointer |
UnliftedRep | unlifted; represented by a pointer |
IntRep | signed, word-sized value |
WordRep | unsigned, word-sized value |
Int64Rep | signed, 64-bit value (on 32-bit only) |
Word64Rep | unsigned, 64-bit value (on 32-bit only) |
AddrRep | A pointer, but not to a Haskell value |
FloatRep | a 32-bit floating point number |
DoubleRep | a 64-bit floating point number |
Length of a SIMD vector type
Element of a SIMD vector type
Int8ElemRep | |
Int16ElemRep | |
Int32ElemRep | |
Int64ElemRep | |
Word8ElemRep | |
Word16ElemRep | |
Word32ElemRep | |
Word64ElemRep | |
FloatElemRep | |
DoubleElemRep |
The Down
type allows you to reverse sort order conveniently. A value of type Down a
contains a value of type a
(represented as Down a
). If a
has an Ord
instance associated with it then comparing two values thus wrapped will give you the opposite of their normal sort order. This is particularly useful when sorting in generalised list comprehensions, as in: then sortWith by Down x
Provides Show
and Read
instances (since: 4.7.0.0).
Since: 4.6.0.0
Down a |
groupWith :: Ord b => (a -> b) -> [a] -> [[a]] Source
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
sortWith :: Ord b => (a -> b) -> [a] -> [a] Source
The sortWith
function sorts a list of elements using the user supplied function to project something out of each element
the :: Eq a => [a] -> a Source
the
ensures that all the elements of the list are identical and then returns that unique element
traceEvent :: String -> IO () Source
Deprecated: Use traceEvent
or traceEventIO
data SpecConstrAnnotation Source
NoSpecConstr | |
ForceSpecConstr |
currentCallStack :: IO [String] Source
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.
Since: 4.5.0.0
data Constraint :: * Source
The kind of constraints, like Show a
type family Any k0 :: k0 where ... Source
The type constructor Any
is type to which you can unsafely coerce any lifted type, and back. More concretely, for a lifted type t
and value x :: t
, -- unsafeCoerce (unsafeCoerce x :: Any) :: t
is equivalent to x
.
The IsList
class and its methods are intended to be used in conjunction with the OverloadedLists extension.
Since: 4.7.0.0
The Item
type function returns the type of items of the structure l
.
fromList :: [Item l] -> l Source
The fromList
function constructs the structure l
from the given list of Item l
fromListN :: Int -> [Item l] -> l Source
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.
toList :: l -> [Item l] Source
The toList
function extracts a list of Item l
from the structure l
. It should satisfy fromList . toList = id.
© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.2.1/docs/html/libraries/base-4.10.0.0/GHC-Exts.html