Skip to content
Snippets Groups Projects

Unlifted newtypes

Closed Andrew Martin requested to merge andrewthad/ghc:unlifted_newtypes into master

Implement the UnliftedNewtypes proposal.

Edited by Andrew Martin

Merge request reports

Loading
Loading

Activity

Filter activity
  • Approvals
  • Assignees & reviewers
  • Comments (from bots)
  • Comments (from users)
  • Commits & branches
  • Edits
  • Labels
  • Lock status
  • Mentions
  • Merge request status
  • Tracking
  • Seems good that we added the DEBUG build to CI as it catches assertion failures with this patch.

  • A big thank you to Andrew for all your work on this patch. I had a good chat about it with Richard today. We can see a way to greatly simplify the gnarly corners of difficultUnliftedNewtype. Stay tuned for more from Richard.

    But meanwhile, thank you.

  • A big thanks to you and Richard and Ryan as well for all your feedback and thoroughness examining this. I'm really happy to hear there's a better way to handle the difficultUnliftedNewtype nastiness.

  • Yes, Simon and I have figured out how to avoid the difficult case, making it go away entirely (that is, accept the programs that are "difficult"), with a minimum of fuss. Would it be OK if I just post an MR against your branch? That seems more efficient than trying to explain the approach.

  • Yes, that would be fine. Also, you should be able to push directly to my branch since I checked the box that allows that. But an MR is fine as well.

  • Matthew Pickering marked as a Work In Progress

    marked as a Work In Progress

  • Ben Gamari changed milestone to %8.10.1

    changed milestone to %8.10.1

  • @rae Sorry I've not followed up on this sooner. Have you had an opportunity out the idea that you and Simon came up with? If not, no worries. If you'd rather punt on improving the error messages for now, we could always use the low-quality error messages that the implementation currently provides, and things could be rewritten later if need be. I think I've got one failing test right now (something that gives a less helpful error message than it should), but I could get that fixed soon.

    Also, over on the differential on phabricator, there were a several problematic interactions with GND that Ryan Scott unearthed, one of which causes a compiler panic. Is there a policy to not merge things that are known to cause panics, or is this something that we could open an issue for and address later?

    I'd like to get this feature wrapped up in the next two weeks since I'm hoping to get the Pointer Rep Proposal done for GHC 8.10, and UnliftedNewtypes is a prerequisite for that proposal.

  • I think I might know what is causing the GND-related panic observed in https://phabricator.haskell.org/D4777#151767. In particular, I think it's this code in TcDerivInfer:

                           -- No constraints for unlifted types
                           -- See Note [Deriving and unboxed types]
                         , not (isUnliftedType arg_ty)

    The isUnliftedType function is partial, and if it's not sure that something is an unlifted type, then it panics. It turns out that levity-polymorphic types are counted as "not sure", so that could very well explain the source of the panic.

    I think it would suffice to use the more conservative check isLiftedType_maybe arg_ty /= Just True instead of not (isUnliftedType arg_ty). Unlike isUnliftedType, isLiftedType_maybe never panics, which should avoid the issue.

    That being said, it turns out that that's not even the only use of isUnliftedType in the deriving-related code in GHC. I count five uses of it in TcGenDeriv and one use in TcGenGenerics. I think it might be worthwhile to replace these with their isLiftedType_maybe equivalents as well.

  • I think it might be worthwhile to replace these with their isLiftedType_maybe equivalents as well.

    Yes -- but perhaps not uncritically. In each of these cases is it legitimate to have a levity-polymorphic type, or should it have been resolved somehow by now.

    Still, using the _maybe version is probably conservative, and will remove crashes.

  • However, that leaves Richard's comment

    Yes, Simon and I have figured out how to avoid the difficult case, making it go away entirely (that is, accept the programs that are "difficult"), with a minimum of fuss. Would it be OK if I just post an MR against your branch? That seems more efficient than trying to explain the approach.

    Richard: I have totally paged this out. What is the issue? How did we solve it? Or what?

    It would be good to help finish up Andrew's work on implementing the unlifted-newtype proposal.

  • Andrew Martin added 1 commit

    added 1 commit

    • ccb121a1 - fix typechecking regressions

    Compare with previous version

  • Andrew Martin added 1 commit

    added 1 commit

    • ae8cf3da - fix issue with interaction between stock deriving and UnliftedNewtypes

    Compare with previous version

  • I've fixed the deriving panic. It only required changing one of the isUnliftedType checks in the deriving code, and the resulting error messages we get are rather good. For example:

    newtype Foo rep = MkFoo (forall (a :: TYPE rep). a)
    deriving stock instance Eq (Foo LiftedRep)

    GHC tells us:

    T15883b.hs:14:1:
         Can't make a derived instance of
            ‘Eq (Foo 'LiftedRep)’ with the stock strategy:
            Don't know how to derive ‘Eq’ for type ‘forall a. a’
         In the stand-alone deriving instance for ‘Eq (Foo LiftedRep)’

    I've added several tests for this to the testsuite.

  • Andrew Martin added 1 commit

    added 1 commit

    • de3d241e - add test to confirm that UnliftedNewtypes do not interfere with payload...

    Compare with previous version

  • Andrew Martin added 1 commit

    added 1 commit

    • b1cb50ca - add -O2 to payload offset test

    Compare with previous version

  • I've added another test to make sure that FFI array payload offsets don't get messed up by newtypes. On another thread, Simon pointed out to me that the the payload offsets are determined by the type constructor in StgCmmForeign:

    add_shim :: DynFlags -> Type -> CmmExpr -> CmmExpr
    add_shim dflags arg_ty expr
      | tycon == arrayPrimTyCon || tycon == mutableArrayPrimTyCon
      = cmmOffsetB dflags expr (arrPtrsHdrSize dflags)
    
      | tycon == smallArrayPrimTyCon || tycon == smallMutableArrayPrimTyCon
      = cmmOffsetB dflags expr (smallArrPtrsHdrSize dflags)
    
      | tycon == byteArrayPrimTyCon || tycon == mutableByteArrayPrimTyCon
      = cmmOffsetB dflags expr (arrWordsHdrSize dflags)
    
      | otherwise = expr

    I thought that UnliftedNewtypes would sneak past this check (since the type constructor doesn't match one of the ones listed in add_shim). But it looks like it doesn't.

  • Andrew Martin added 1 commit

    added 1 commit

    • 6c04a69d - Implement UnliftedNewtypes extension

    Compare with previous version

  • I've rebased on top of master. There are two regressions in the test suite, both for tests that were added as a part of this MR. The failing tests are UnliftedNewtypesMismatchedKindRecord and UnliftedNewtypesMismatchedKind. The error message has degraded from the helpful

    Expecting a lifted type, but ‘Int#’ is unlifted ...

    To the horrible

    Kind unification on the result kind a newtype is not yet sophisticated ...

    It's possible that I goofed somewhere when resolving the merge conflicts. One other thing I can think of that could cause this is if unifyKind was changed to no longer fail immidiately on an insoluble constraint. It seems unlikely that this change would have been made.

  • Actually, I think unifyKind has been changed. With typechecker tracing enabled, I can see:

    +unifyNewtypeKind *
    +ukind
    +  *
    +  TYPE 'IntRep
    +  Nothing
    +u_tys
    +  tclvl 1
    +  * ~ TYPE 'IntRep
    +  arising from a type equality * ~ TYPE 'IntRep
    +u_tys
    +  tclvl 1
    +  'LiftedRep ~ 'IntRep
    +  arising from a type equality * ~ TYPE 'IntRep
    +New coercion hole: co_aZP
    +utype_defer
    +  'LiftedRep
    +  'IntRep
    +  arising from a type equality * ~ TYPE 'IntRep
    +  In the definition of data constructor ‘MkT’
    +  In the newtype declaration for ‘T’
    +utype_defer2 {co_aZP}
    +u_tys yields coercion: {co_aZP}
    +u_tys yields coercion: (TYPE {co_aZP})_N
    +Adding
    +  UnliftedNewtypesMismatchedKind.hs:12:3:
    +       Kind unification on the result kind a newtype is not yet

    GHC discovers the constraint 'LiftedRep ~ 'IntRep and then doesn't fail. It used to fail before I rebased. I'm not sure what has changed in GHC, but I'm guessing the UnliftedNewtypes code will need some reengineering to accommodate this change.

  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
Please register or sign in to reply
Loading