Desugaring matches with already-desugared RHSs?

Simon Peyton Jones simonpj at microsoft.com
Mon Apr 27 09:04:02 UTC 2020


Alexis

We have

data MatchGroup p body
  = MG { mg_ext     :: XMG p body -- Post-typechecker, types of args and result
       , mg_alts    :: Located [LMatch p body]  -- The alternatives
       , mg_origin  :: Origin }

explicitly parameterised over 'body'.  And we use that parameterisation:

  | HsLam     (XLam p)
              (MatchGroup p (LHsExpr p))
	
  | HsCmdLam    (XCmdLam id)
                (MatchGroup id (LHsCmd id))     -- kappa


So it makes perfect sense to me that the desugarer for MatchGroup should be parameterised with a function for desugaring 'body'.

(Let's be consistent about whether we use 'rhs' or 'body' for this parmemeterisation.)

TL;DR: Yes, what you suggest sounds sensible to me.

Simon

|  -----Original Message-----
|  From: ghc-devs <ghc-devs-bounces at haskell.org> On Behalf Of Alexis King
|  Sent: 26 April 2020 02:40
|  To: ghc-devs <ghc-devs at haskell.org>
|  Subject: Desugaring matches with already-desugared RHSs?
|  
|  Hi all,
|  
|  I’m currently in the process of rewriting most of the arrow desugaring
|  code. One of the most awkward parts of the current implementation is
|  the way case commands are desugared. Given a case command like
|  
|      case e1 of
|        A a b   -> cmd1
|        B c     -> cmd2
|        C d e f -> cmd3
|  
|  the desugarer actually replaces each command on the RHS with an
|  Either-wrapped tuple to get something like this:
|  
|      arr (\env -> case e1 of
|            A a b   -> Left (Left (a, b))
|            B c     -> Left (Right c)
|            C d e f -> Right (d, e, f))
|      >>> ((cmd1 ||| cmd2) ||| cmd3)
|  
|  This means the RHSs of the case expression are really already
|  desugared, and ideally they would be CoreExprs, but matchWrapper
|  expects the RHSs to be HsExprs. The current implementation
|  accommodates this restriction by building fake HsExprs with no
|  location information, but this means the logic for building the tuples
|  in the RHSs has to be duplicated (since other places do want
|  CoreExprs).
|  
|  I was thinking it would be nice to avoid this hack, but I’m not sure
|  what the best way to do it is. One way would be to create a variant of
|  matchWrapper with a type like
|  
|      matchWrapper'
|        :: HsMatchContext GhcRn
|        -> Maybe (LHsExpr GhcTc)
|        -> MatchGroup GhcTc rhs
|        -> (rhs -> DsM CoreExpr)  -- how to desugar the RHSs
|        -> DsM ([Id], CoreExpr)
|  
|  and update dsGRHSs to accept an extra argument as well. Then the arrow
|  desugaring code could just pass `return` to matchWrapper' so it
|  wouldn’t touch its RHSs. But I’m not sure if this approach makes sense
|  — nothing else in the desugarer seems to work this way. Is there a
|  better approach I’m not seeing?
|  
|  Thanks,
|  Alexis
|  _______________________________________________
|  ghc-devs mailing list
|  ghc-devs at haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.has
|  kell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devs&data=02%7C01%7Csimonpj%40microsoft.com%7C4a68eaa5bad44aef3cdc08d
|  7e982ca00%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637234620252546061
|  &sdata=98tG%2FVS91GWHX4xqIulr7h6H%2Fl%2F2VIDwYmSOAke%2BZ0w%3D&res
|  erved=0


More information about the ghc-devs mailing list