ghc-prim-0.5.0.0: GHC primitives

Copyright(c) The University of Glasgow 2009
Licensesee libraries/ghc-prim/LICENSE
Maintainercvs-ghc@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell2010

GHC.Types

Contents

Description

GHC type definitions. Use GHC.Exts from the base package instead of importing this module directly.

Synopsis

Documentation

data Bool Source

Constructors

False 
True 

data Char Source

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

Constructors

C# Char# 

data Int Source

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.

Constructors

I# Int# 

data Word Source

A Word is an unsigned integral type, with the same size as Int.

Constructors

W# Word# 

data Float Source

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.

Constructors

F# Float# 

data Double Source

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.

Constructors

D# Double# 

data Ordering Source

Constructors

LT 
EQ 
GT 

newtype IO a Source

A value of type IO a is a computation which, when performed, does some I/O before returning a value of type a.

There is really only one way to "perform" an I/O action: bind it to Main.main in your program. When your program is run, the I/O will be performed. It isn't possible to perform I/O from an arbitrary function, unless that function is itself in the IO monad and called at some point, directly or indirectly, from Main.main.

IO is a monad, so IO actions can be combined using either the do-notation or the >> and >>= operations from the Monad class.

Constructors

IO (State# RealWorld -> (#State# RealWorld, a#)) 

isTrue# :: Int# -> Bool Source

Alias for tagToEnum#. Returns True if its parameter is 1# and False if it is 0#.

data SPEC Source

SPEC is used by GHC in the SpecConstr pass in order to inform the compiler when to be particularly aggressive. In particular, it tells GHC to specialize regardless of size or the number of specializations. However, not all loops fall into this category.

Libraries can specify this by using SPEC data type to inform which loops should be aggressively specialized.

Constructors

SPEC 
SPEC2 

data Nat Source

(Kind) This is the kind of type-level natural numbers.

data Symbol Source

(Kind) This is the kind of type-level symbols. Declared here because class IP needs it

class a ~~ b 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.

class Coercible a b 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 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

data Levity Source

GHC divides all proper types (that is, types that can perhaps be inhabited, as distinct from type constructors or type-level data) into two worlds: lifted types and unlifted types. For example, Int is lifted while Int# is unlifted. Certain operations need to be polymorphic in this distinction. A classic example is unsafeCoerce#, which needs to be able to coerce between lifted and unlifted types. To achieve this, we use kind polymorphism: lifted types have kind TYPE Lifted and unlifted ones have kind TYPE Unlifted. Levity is the kind of Lifted and Unlifted. * is a synonym for TYPE Lifted and # is a synonym for TYPE Unlifted.

Constructors

Lifted 
Unlifted 

type Type = TYPE Lifted Source

The kind of types with values. For example Int :: Type.

type * = TYPE Lifted Source

A backward-compatible (pre-GHC 8.0) synonym for Type

type (★) = TYPE Lifted Source

A unicode backward-compatible (pre-GHC 8.0) synonym for Type

data Constraint Source

The kind of constraints, like Show a

Runtime type representation

data Module Source

Constructors

Module TrName TrName 

data TrName Source

Constructors

TrNameS Addr# 
TrNameD [Char]