ghc-9.4.3: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Builtin.Types

Description

This module is about types that can be defined in Haskell, but which must be wired into the compiler nonetheless. C.f module GHC.Builtin.Types.Prim

Synopsis

Helper functions defined here

All wired in things

isBuiltInOcc_maybe :: OccName -> Maybe Name Source #

Built-in syntax isn't "in scope" so these OccNames map to wired-in Names with BuiltInSyntax. However, this should only be necessary while resolving names produced by Template Haskell splices since we take care to encode built-in syntax names specially in interface files. See Note [Symbol table representation of names].

Moreover, there is no need to include names of things that the user can't write (e.g. type representation bindings like $tc(,,,)).

Bool

Ordering

Boxing primitive types

Char

Double

Float

Int

Word

Word8

List

mkPromotedListTy Source #

Arguments

:: Kind

of the elements of the list

-> [Type]

elements

-> Type 

Make a *promoted* list.

NonEmpty

Maybe

Tuples

mkTupleTy :: Boxity -> [Type] -> Type Source #

Make a tuple type. The list of types should not include any RuntimeRep specifications. Boxed 1-tuples are flattened. See Note [One-tuples]

mkTupleTy1 :: Boxity -> [Type] -> Type Source #

Make a tuple type. The list of types should not include any RuntimeRep specifications. Boxed 1-tuples are *not* flattened. See Note [One-tuples] and Note [Don't flatten tuples from HsSyn] in GHC.Core.Make

mkBoxedTupleTy :: [Type] -> Type Source #

Build the type of a small tuple that holds the specified type of thing Flattens 1-tuples. See Note [One-tuples].

unboxedTupleKind :: [Type] -> Kind Source #

Specialization of unboxedTupleSumKind for tuples

unboxedSumKind :: [Type] -> Kind Source #

Specialization of unboxedTupleSumKind for sums

filterCTuple :: RdrName -> RdrName Source #

Replaces constraint tuple names with corresponding boxed ones.

Constraint tuples

cTupleTyConNameArity_maybe :: Name -> Maybe Arity Source #

If the given name is that of a constraint tuple, return its arity.

Any

Recovery TyCon

makeRecoveryTyCon :: TyCon -> TyCon Source #

Make a fake, recovery TyCon from an existing one. Used when recovering from errors in type declarations

Sums

sumTyCon :: Arity -> TyCon Source #

Type constructor for n-ary unboxed sum.

sumDataCon :: ConTag -> Arity -> DataCon Source #

Data constructor for i-th alternative of a n-ary unboxed sum.

Kinds

liftedRepTyCon :: TyCon Source #

type LiftedRep = 'BoxedRep 'Lifted

unliftedRepTyCon :: TyCon Source #

type UnliftedRep = 'BoxedRep 'Unlifted

unliftedTypeKindTyCon :: TyCon Source #

type UnliftedType = TYPE ('BoxedRep 'Unlifted)

Equality predicates

RuntimeRep and friends

Multiplicity and friends

Bignum