Skip to content

Draft: Allow top-level unlifted types in Core

Jaro Reinders requested to merge wip/T17521 into master

See

This already works for simple cases like this:

{-# LANGUAGE UnliftedDatatypes #-}

module Test where

import GHC.Exts
import Data.Kind
-- type UnliftedType = Type

type Box :: UnliftedType -> Type
data Box a = Box a
type UNat :: UnliftedType
data UNat = USucc UNat | UZero

x :: Box UNat
x = Box (USucc (USucc UZero))

That gets compiled to this Cmm:

==================== Output Cmm ====================
[section ""data" . UZero_closure" {
     UZero_closure:
         const UZero_con_info;
 }]



==================== Output Cmm ====================
[section ""data" . x2_closure" {
     x2_closure:
         const USucc_con_info;
         const UZero_closure+2;
         const 3;
 }]



==================== Output Cmm ====================
[section ""data" . x1_closure" {
     x1_closure:
         const USucc_con_info;
         const x2_closure+1;
         const 3;
 }]



==================== Output Cmm ====================
[section ""data" . x_closure" {
     x_closure:
         const Box_con_info;
         const x1_closure+1;
         const 3;
 }]

TODO:

  • Check if we still need to ANFise.
  • More tests?
  • Assertion that unlifted bindings do not end up in boot files or in general in interfaces without tag information. (instead of an assertion, I've added a STG lint that runs after tag inference)
  • Write a compelling use-case that shows a significant performance increase
  • Check if this can be problematic for the bytecode interpreter cf. !10417
  • Investigate if this could cause pointer tagging issues
  • Update exprIsTopLevelBindable and the letrec invariant and associated lint to account for the new spec in #23637 (I've implemented a different invariant, I'll update the relevant places later)
  • Check all references to the core letrec invariant
  • Fix problems in bytecode interpreter (implement recursive linking)
  • Check if indirections are a problem
  • Agree on invariant and naming
  • Split core lint for let-can-float and letrec invariants into two separate things (#23637 (comment 522452))
  • Rename StgTopLifted or introduce new constructor.
Edited by Jaro Reinders

Merge request reports