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

GHC.Stg.Lint

Description

(c) The GRASP/AQUA Project, Glasgow University, 1993-1998

A lint pass to check basic STG invariants:

  • Variables should be defined before used.
  • Let bindings should not have unboxed types (unboxed bindings should only appear in case), except when they're join points (see Note [Core let/app invariant] and #14117).
  • If linting after unarisation, invariants listed in Note [Post-unarisation invariants].

Because we don't have types and coercions in STG we can't really check types here.

Some history:

StgLint used to check types, but it never worked and so it was disabled in 2000 with this note:

WARNING: ~~~~~~~~

This module has suffered bit-rot; it is likely to yield lint errors for Stg code that is currently perfectly acceptable for code generation. Solution: don't use it! (KSW 2000-05).

Since then there were some attempts at enabling it again, as summarised in #14787. It's finally decided that we remove all type checking and only look for basic properties listed above.

Note [Linting StgApp] ~~~~~~~~~~~~~~~~~~~~~ To lint an application of the form `f a_1 ... a_n`, we check that the representations of the arguments a_1, ..., a_n match those that the function expects.

More precisely, suppose the types in the application `f a_1 ... a_n` are as follows:

f :: t_1 -> ... -> t_n -> res a_1 :: s_1, ..., a_n :: s_n

t_1 :: TYPE r_1, ..., t_n :: TYPE r_n s_1 :: TYPE p_1, ..., a_n :: TYPE p_n

Then we must check that each r_i is compatible with s_i. Compatibility is weaker than on-the-nose equality: for example, IntRep and WordRep are compatible. See Note [Bad unsafe coercion] in GHC.Core.Lint.

Wrinkle: it can sometimes happen that an argument type in the type of the function does not have a fixed runtime representation, i.e. there is an r_i such that runtimeRepPrimRep r_i crashes. See https://gitlab.haskell.org/ghc/ghc/-/issues/21399 for an example. Fixing this issue would require significant changes to the type system of STG, so for now we simply skip the Lint check when we detect such representation-polymorphic situations.

Note [Typing the STG language] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In Core, programs must be well-typed. So if f :: ty1 -> ty2, then in the application (f e), we must have e :: ty1

STG is still a statically typed language, but the type system is much coarser. In particular, STG programs must be well-kinded. More precisely, if f :: ty1 -> ty2, then in the application (f e) where e :: ty1', we must have kind(ty1) = kind(ty1').

So the STG type system does not distinguish beteen Int and Bool, but it does distinguish beteen Int and Int#, because they have different kinds. Actually, since all terms have kind (TYPE rep), we might say that the STG language is well-runtime-rep'd.

This coarser type system makes fewer distinctions, and that allows many nonsensical programs (such as (x && "foo")) -- but all type systems accept buggy programs! But the coarseness also permits some optimisations that are ill-typed in Core. For example, see the module STG.CSE, which is all about doing CSE in STG that would be ill-typed in Core. But it must still be well-kinded!

Documentation

lintStgTopBindings Source #

Arguments

:: forall a. (OutputablePass a, BinderP a ~ Id) 
=> Platform 
-> Logger 
-> DiagOpts 
-> StgPprOpts 
-> InteractiveContext 
-> Module

module being compiled

-> Bool

have we run Unarise yet?

-> String

who produced the STG?

-> [GenStgTopBinding a] 
-> IO ()