[GHC] #12618: Add saturated constructor applications to Core

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- A long-standing performance bug in GHC is its behaviour on nested tuples. * The poster-child case is #5642. * The problem is that when you have a nested tuple application, e.g. `((4,True),('c','d'))`, the size of the type arguments grows quadratically with the expression size. This bites badly in some approaches to generic programming, which use nested tuples heavily. * It's explained in detail in Section 2.3 of [http://research.microsoft.com/en- us/um/people/simonpj/papers/variant-f/index.htm Scrap your type applications]. The same paper describes a solution, a modification of System F called System IF. It's neat, and I did once implement in in GHC. But it was quite complicated; most of the time the win was not big; and I don't know how it'd interact with casts, coercions, and type dependency in the latest version of GHC's Core. So here's another idea, which came up in converstion at ICFP'16: '''add a staturated constructor application to Core'''. So Core looks like {{{ data Expr v = Var v | App (Expr v) (Expr v) ... | ConApp DataCon [Expr v] -- NEW }}} Now I hate the idea of adding a new constructor to Core; I often brag about how few constructors it has. But the idea is this: * A `ConApp` is always saturated; think of it as an uncurried application. * Every data constructor has a wrapper Id. For simple constructors like `(:)`, the wrapper is just a curried version: {{{ (:) = /\a. \(x:a). \(y:[a]). (:) [x,y] }}} where the "`(:) [x,y]`" is just my concrete syntax for a `ConApp` node. * We are used to having an intro and elim form for each type former. So for `(->)` the intro form is `\x.e` and the elim form is `(e1 e2)`. For a data type like `Maybe`, the elim form is `case`, but what's the intro form? `ConApp` of course. * A `ConApp` mentions the `DataCon` explicitly, rather than having it buried inside the `IdDetails` of an `Id`, which somehow seems more honest. The proximate reason for doing this in the first place is to allow us to omit type arguments. Consider `Just True`. Curently we represent this as {{{ Var "Just" `App` Type boolTy `App` Var "True" }}} But with `ConApp` we can say {{{ ConApp "Just" [ConApp "True" []] }}} because it's easy to figure out the `boolTy` type argument from the argument. (We don't really have strings there, but you get the idea.) Can we omit ''all'' the type arguments? No: we can omit only those that appear free in any of the argument types. That is usally all of them (including existentials) but not always. Consider: {{{ data (,) a b where (,):: forall a b. a -> b -> (a,b) data [] a where [] :: forall a. [a] (:) :: forall a. a -> [a] -> [a] data Either a b where Left :: forall a b. a -> Either a b Right :: forall a b. b -> Either a b data (:=:) a b where Refl :: forall a b. (a~b) -> :=: a b data Foo where MkFoo :: a -> (a -> Int) -> Foo }}} For all of these data constructors except `[]` (nil), `Left` and `Right` we can omit all the type arguments, because we can recover them by simple matching against the types of the arguments. A very concrete way to think about this is how to implement {{{ exprType :: Expr Id -> Type exprType (Var v) = varType v exprType (Lam b e) = mkFunTy (varType b) (exprType e) exprType (App f a) = funResultTy (exprType f) ... exprType (ConApp con args) = mkTyConApp (dataConTyCon con) ??? }}} We know that the result type of type of a `ConApp` will be `T t1 ..tn` where `T` is the parent type constructor of the `DataCon`. But what about the (universal) type args `???`? We can get them from the types of the arguments `map exprType args`: * For `ConApp "(:)" [e1, e2]`, the type arument is just `exprType e1`. * For `ConApp "(:=:)" [e]`", we expect `exprType e` to return a type looking like `TyConApp "~" [t1, t2]`. Then `t1` and `t2` are the types we want. So matching is required. * What about an application of `Left`?? We need to recover two type args, but `exprType e1` gives us only one. So we must retain the other one in the application: `ConApp "Left" [Type ty2, e1]`. Similarly for the empty list. A simple once-and-for-all analyis on the `DataCon` will establish how to do the matching, which type args to retain, etc. Tradeoffs: * Pro: We can eliminate almost all type args of almost all data constructors; and for nested tuples we can eliminate all of them. * Pro: it's elegant having the intro/elim duality. * Pro: in GHC we often ask "is this expression a saturated constructor application?" (see `exprIsConApp_maybe`) and `ConApp` makes it easier to answer that question. * Pro: we do exactly this in types: we have `AppTy` and `TyConApp`. (In types a `TyConApp` is not required to be satureted, but we could review that choice.) * Con: adding a constructor is a big deal. In lots of places we'd end up saying {{{ f (App e1 e2) = App (f e1) (f e2) f (ConApp c es) = ConApp c (map f es) }}} In the olden days GHC's `App` had multiple arguments and the continual need to work over the list was a bit tiresome. Still `ConApp` is very simple and uniform; quite often adding `map` won't be difficult; and it may well be that constructors need to be treated differently anyway. * Con: it's not a general solution to the type-argument problem. See #9198 for example. System IF is the only general solution I know, but it seems like too big a sledgehammer. We'll only know if we try it. I estimiate that it would take less than a week to work this change through all of GHC. 90% of it is routine. Other possibly-relevant tickets are #8523, #7428, #9630. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * cc: mpickering (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * cc: osa1 (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): What is special about a data constructor that allows this, that a function (like, say, `flip`) does not have? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by chak): * cc: chak (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * cc: niteria (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kosmikus): * cc: kosmikus (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Replying to [comment:5 nomeata]:
What is special about a data constructor that allows this, that a function (like, say, `flip`) does not have?
Let me try to answer that myself: Essentially, you are proposing a way of compressing the representation of Core, by omitting (type) arguments that can easily and in a syntax- directed manner be recovered. You are implying here the existence of a pair of functions {{{ compressArgs :: DataCon -> [Expr v] -> [Expr v] decompressArgs :: DataCon -> [Expr v] -> [Expr v] }}} that remove and recover implied arguments. For example `compressArgs "Left" [Bool,Int,True] = [Bool, True]`. We obviously want to following identity to hold: {{{ length args == dcArity dc ==> decompressArgs dc (compressArgs dc args) == args }}} What does `compressArgs` and `decompressArgs` need from `DataCon`? Two bits of information: * It’s type (`forall a b. a -> Either a b`) and * its arity (3, counting type arguments). Well, `compressArgs` does not need the arity, because it is just the length of the input list, if the application is saturated. But `decompressArgs` does (why? see example later). So really, we have a pair of functions {{{ compressArgs :: Type -> [Expr v] -> [Expr v] decompressArgs :: Type -> Arity -> [Expr v] -> [Expr v] }}} Here, we want {{{ decompressArgs ty (length args) (compressArgs ty args) == args }}} And with this I can see how the above proposal easily generalizes to functions: Have {{{ | Apps (Expr v) Arity [Expr v] -- NEW }}} Instead of {{{f `App` x `App` y `App` z}}} you can use `Apps f 3 (compressArgs (exprType f) [x,y,z])`. No information is lost (because of the above identity), but any redundant information can be removed by `compressArgs`. Why do we need to store the arity? Because `compressArgs` can produce the same compressed list for different input lists: {{{ compressArgs "forall a. a -> a" [Bool,True] == [True] compressArgs "forall a. a -> a" [Bool] == [Bool] compressArgs "forall a. a -> a" [Type, Bool] == [Bool] }}} I imagine getting rid of all (well, many more) of the redundant type applications throughout Core can be big win, so maybe this generalization should be considered. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Oh, and fun fact: It might be possible to remove `App` completely and replace it with a pattern synonym here: Due to `compressArgs ty [x] = [x]`, `Apps f 1 [e]` is equivalent to `App f e`. So this might not actually be a serious change to core, nor might it be increasing the number of constructors: Using a bidirectional smart constructor (which does optimizes the representation under the hood) this can hopefully be a completely transparent optimization of the representation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): I'd like to chime in and agree that it would be a good design to reflect saturated function application and related info into a corresponding multi arg saturated app application form. I've some woke in progress type theory developments critically use having a built in motion of simultaneous arguments and results (a la types are calling conventions or sequent core), where the logical strength of what can be described needs a built in motion of simultaneous arguments. I presume / assume this multi arg app form is essentially a function application against an unboxed tuple? Right? One thing I'd like to point out is that a knock on effect of this change you may want to consider is having Unboxed tuples in arg and return positions act like pi and sigma telescopes respectively. If what I'm sketching out needs more clarity, I'm happy to do a clearer exposition on the wiki or the like If the meat of the ideas discussed / articulated are consistent with / facilitated by the details I'm hopefully articulating clearly, this would be a set of changes I would strongly support. In. Fact I could probably get support for putting work time into helping out on this change if need be. Partly because then certain ideas I would like to experimentally add to ghc would then be much much easier to add :) (The simultaneous arguments stuff makes embedding / supporting linear logical stuff in a clean way much nicer than previous efforts p) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by heisenbug: @@ -19,1 +19,1 @@ - So here's another idea, which came up in converstion at ICFP'16: '''add a + So here's another idea, which came up in conversation at ICFP'16: '''add a @@ -97,1 +97,1 @@ - * For `ConApp "(:)" [e1, e2]`, the type arument is just `exprType e1`. + * For `ConApp "(:)" [e1, e2]`, the type argument is just `exprType e1`. @@ -108,1 +108,1 @@ - A simple once-and-for-all analyis on the `DataCon` will establish how to + A simple once-and-for-all analysis on the `DataCon` will establish how to @@ -124,1 +124,1 @@ - types a `TyConApp` is not required to be satureted, but we could review + types a `TyConApp` is not required to be saturated, but we could review @@ -142,1 +142,1 @@ - We'll only know if we try it. I estimiate that it would take less than a + We'll only know if we try it. I estimate that it would take less than a New description: A long-standing performance bug in GHC is its behaviour on nested tuples. * The poster-child case is #5642. * The problem is that when you have a nested tuple application, e.g. `((4,True),('c','d'))`, the size of the type arguments grows quadratically with the expression size. This bites badly in some approaches to generic programming, which use nested tuples heavily. * It's explained in detail in Section 2.3 of [http://research.microsoft.com/en- us/um/people/simonpj/papers/variant-f/index.htm Scrap your type applications]. The same paper describes a solution, a modification of System F called System IF. It's neat, and I did once implement in in GHC. But it was quite complicated; most of the time the win was not big; and I don't know how it'd interact with casts, coercions, and type dependency in the latest version of GHC's Core. So here's another idea, which came up in conversation at ICFP'16: '''add a staturated constructor application to Core'''. So Core looks like {{{ data Expr v = Var v | App (Expr v) (Expr v) ... | ConApp DataCon [Expr v] -- NEW }}} Now I hate the idea of adding a new constructor to Core; I often brag about how few constructors it has. But the idea is this: * A `ConApp` is always saturated; think of it as an uncurried application. * Every data constructor has a wrapper Id. For simple constructors like `(:)`, the wrapper is just a curried version: {{{ (:) = /\a. \(x:a). \(y:[a]). (:) [x,y] }}} where the "`(:) [x,y]`" is just my concrete syntax for a `ConApp` node. * We are used to having an intro and elim form for each type former. So for `(->)` the intro form is `\x.e` and the elim form is `(e1 e2)`. For a data type like `Maybe`, the elim form is `case`, but what's the intro form? `ConApp` of course. * A `ConApp` mentions the `DataCon` explicitly, rather than having it buried inside the `IdDetails` of an `Id`, which somehow seems more honest. The proximate reason for doing this in the first place is to allow us to omit type arguments. Consider `Just True`. Curently we represent this as {{{ Var "Just" `App` Type boolTy `App` Var "True" }}} But with `ConApp` we can say {{{ ConApp "Just" [ConApp "True" []] }}} because it's easy to figure out the `boolTy` type argument from the argument. (We don't really have strings there, but you get the idea.) Can we omit ''all'' the type arguments? No: we can omit only those that appear free in any of the argument types. That is usally all of them (including existentials) but not always. Consider: {{{ data (,) a b where (,):: forall a b. a -> b -> (a,b) data [] a where [] :: forall a. [a] (:) :: forall a. a -> [a] -> [a] data Either a b where Left :: forall a b. a -> Either a b Right :: forall a b. b -> Either a b data (:=:) a b where Refl :: forall a b. (a~b) -> :=: a b data Foo where MkFoo :: a -> (a -> Int) -> Foo }}} For all of these data constructors except `[]` (nil), `Left` and `Right` we can omit all the type arguments, because we can recover them by simple matching against the types of the arguments. A very concrete way to think about this is how to implement {{{ exprType :: Expr Id -> Type exprType (Var v) = varType v exprType (Lam b e) = mkFunTy (varType b) (exprType e) exprType (App f a) = funResultTy (exprType f) ... exprType (ConApp con args) = mkTyConApp (dataConTyCon con) ??? }}} We know that the result type of type of a `ConApp` will be `T t1 ..tn` where `T` is the parent type constructor of the `DataCon`. But what about the (universal) type args `???`? We can get them from the types of the arguments `map exprType args`: * For `ConApp "(:)" [e1, e2]`, the type argument is just `exprType e1`. * For `ConApp "(:=:)" [e]`", we expect `exprType e` to return a type looking like `TyConApp "~" [t1, t2]`. Then `t1` and `t2` are the types we want. So matching is required. * What about an application of `Left`?? We need to recover two type args, but `exprType e1` gives us only one. So we must retain the other one in the application: `ConApp "Left" [Type ty2, e1]`. Similarly for the empty list. A simple once-and-for-all analysis on the `DataCon` will establish how to do the matching, which type args to retain, etc. Tradeoffs: * Pro: We can eliminate almost all type args of almost all data constructors; and for nested tuples we can eliminate all of them. * Pro: it's elegant having the intro/elim duality. * Pro: in GHC we often ask "is this expression a saturated constructor application?" (see `exprIsConApp_maybe`) and `ConApp` makes it easier to answer that question. * Pro: we do exactly this in types: we have `AppTy` and `TyConApp`. (In types a `TyConApp` is not required to be saturated, but we could review that choice.) * Con: adding a constructor is a big deal. In lots of places we'd end up saying {{{ f (App e1 e2) = App (f e1) (f e2) f (ConApp c es) = ConApp c (map f es) }}} In the olden days GHC's `App` had multiple arguments and the continual need to work over the list was a bit tiresome. Still `ConApp` is very simple and uniform; quite often adding `map` won't be difficult; and it may well be that constructors need to be treated differently anyway. * Con: it's not a general solution to the type-argument problem. See #9198 for example. System IF is the only general solution I know, but it seems like too big a sledgehammer. We'll only know if we try it. I estimate that it would take less than a week to work this change through all of GHC. 90% of it is routine. Other possibly-relevant tickets are #8523, #7428, #9630. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): There are two different things that are orthogonal: * Enforcing saturated function calls (types are calling convention etc.), which this ticket is ''not'' about about. * Here, we want to avoid storing redundant types arguments. As this can be implemented with pattern synonyms, this should be a semantically transparent change. The former is also interesting (and there is some simplicity to be gained by having both, as the arity of a function application would be determined by the function’s type), but let’s keep them separate for now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Using a pattern synonynm works always; the problem is that the code should be generic in the binder, but then we have no way of knowing the binder’s type. But for what it’s worth: It seems to compile with this change: {{{ data Expr b = Var Id | Lit Literal -- | App (Expr b) (Arg b) | Apps (Expr b) Arity [Expr b] | Lam b (Expr b) | Let (Bind b) (Expr b) | Case (Expr b) b Type [Alt b] -- See #case_invariant# | Cast (Expr b) Coercion | Tick (Tickish Id) (Expr b) | Type Type | Coercion Coercion deriving Data unpackArgs :: Expr b -> Arity -> [Expr b] -> [Expr b] unpackArgs _ _ l = l -- do something smarter here packArgs :: Expr b -> [Expr b] -> [Expr b] packArgs _ l = l -- do something smarter here popArg :: Expr b -> Maybe (Expr b, Expr b) popArg (Apps e a xs) = case unpackArgs e a xs of [x] -> Just (e, x) xs -> Just (Apps e (a-1) (packArgs e (init xs)), last xs) popArg _ = Nothing pattern App e1 e2 <- (popArg -> Just (e1, e2)) where App e1 e2 | (f, args) <- collectArgs e1 = Apps f (length args +1) (packArgs f (args ++ [e2])) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I guess the solution to that is adding a type class, such as {{{ class CompressArgs b where unpackArgs :: Expr b -> Arity -> [Expr b] -> [Expr b] unpackArgs _ _ l = l packArgs :: Expr b -> [Expr b] -> [Expr b] packArgs _ l = l }}} or alternatively {{{ class HasType a where hasType :: Expr a -> Type }}} and adding instances for the two type of binders we have (`Var` and `TaggedBndr t`). With a few constraints added in various places (four modules only), this also compiles. It seems the remaining bit is to solve the staging issue: The instance should live in `CoreSyn`, but requires `expType` in `CoreUtils`. If that can be solved, the feature could be added quite painlessly. Then, in all places where the expression is traversed, one can any time make the decision to work on `Apps` directly, instead of `App`. I expect we’d get the memory performance boost we want (exciting!), but I also expect that this encoding/decoding in every traversal will cost runtime. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Let's not go overboard here! This ticket is ''only'' about treating '''saturated''' applications of '''data constructors''' specially. There are two more ambitious possible * Try to suppress more type arguments, for situations other than saturated data constructors. If you are interested in that, please read [https://www.microsoft.com/en-us/research/publication/scrap-your-type- applications/ Scrap your type applications]. By all means come up with a better scheme, but that paper describes the best one I know. * Introduce uncurried application as a Core primitive (and eliminate `App`). For that we'd want uncurried lambda as well (the intro form). Please read [https://www.microsoft.com/en-us/research/publication/types- are-calling-conventions/ Types are calling conventions]. I talked with Stephanie and Joachim about this at ICFP, and I think Joachim is going to follow it up. It too involves complications (notably abstraction must be over a telescope), and we had an alternative idea with "computation types". More on that anon, doubtless. By all means start new tickets to discuss these generalisations. But ''this'' ticket is just about the intro-form that is dual to `case`, namely saturated constructor application. If we discuss the (much more ambitious) generalisations here, the payload of this ticket will get buried. (One reason for NOT adopting `ConApp` is that it might ultimately be subsumed by the more general cases. But I'm not holding my breath.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): I exactly want those unboxed tuple telescopes :) Fair enough I'll see if I can put together an exposition that cleans up tacc and articulates some changes which make it nicer -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I guess I did get a bit overly excited, on the way back from ICFP. I moved all my comments about generalizing this to arbitrary applications in an transparent way to #12626. But I still wonder what’s so special about data constructors, and why whatever works for data constructors does not work in general. I skimmed the paper, and will read it more carefully again now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by lukemaurer): We went back and forth with something like this in Sequent Core, where having the dual of Case was nice. One downside hasn't been mentioned, though: We'll need to use smart constructors more consistently, or otherwise not be able to count on ''all'' saturated constructor applications to use `ConApp`. Currently there's `mkCoreApp` and `mkCoreApps`, but those are only necessary when the let/app invariant must be enforced; IIRC, lots of places where let/app is known to hold just use fold `App` over the arguments. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): simonpj says:
A simple once-and-for-all analysis on the DataCon will establish how to do the matching, which type args to retain, etc.
So a `DataCon` will have this info stored in it? It might be non-trivial! For example: {{{ data T a where MkT :: F a -> T a }}} If `F` is not injective, we would need to store the choice for `a`. Even if it is injective, it may be more convenient to store the choice for `a`. And then there are examples like {{{ data T2 a where MkT2 :: Maybe (Either Bool a -> a) -> T2 a }}} where the relationship between the constructor field's type and the choice for `a` is non-trivial. However, perhaps a use of `tcMatchTy` or one of its friends when constructing the `DataCon` is enough to sort this out. If we successfully do this for data constructors, it should not be hard to do the same for poly-kinded type constructors. I'm specifically thinking about the redundant `RuntimeRep` arguments to unboxed-tuple type constructors. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by michalt): * cc: michalt (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * owner: => nomeata Comment: JFTR, I’m working on implementing this. Not sure if one week is enough, there seems to be an endless supplies of code paths that have a catch-all pattern match on `CoreExpr` and thus are not found by the compiler. My work is in `wip/T12618`. Stage 1 compiles, and seems to work mostly, but if I build ghc-stage2 with it, `ghc-stage2` crashes with an `internal error: evacuate(static): strange closure type 0`. If someone enjoys debugging these kind of problems, let me know... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): It seems I get `internal error: evacuate(static): strange closure type 0` only with a dynamically built GHC, not with a statically built (as it is the case on Travis). If that rings a bell with someone that could save me further debugging work, I’d be grateful. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): While I make progress with getting the tree to compiler properly again, here is one question that will need to be answered. Consider this rule: {{{ "foldr/id" foldr (:) [] = \x -> x }}} Because we desugar constructor in source to the ''wrapper'' (especially if they are unsaturated), but the wrapper is a function that will be marked as inlineable, the compiler now gives this error message: {{{ libraries/base/GHC/Base.hs:855:1: warning: [-Winline-rule-shadowing] Rule "foldr/id" may never fire because ‘GHC.Types.$W:’ might inline first Probable fix: add an INLINE[n] or NOINLINE[n] pragma for ‘GHC.Types.$W:’ }}} So at first I thought: Ok, no problem, I just force the inlining of data con wrappers after the desugaring of rule left-hand sides, and this might work for `[]`, but `(:)` is really used unsaturated here. What is the best way forward here? One way would be to disable this warning specifically for datacon workers, and then make the rule matcher smart enough to match both variants. Or alternatively, make the warning aware that an unsaturated use of a function with an unfolding will not inline, and it is thus ok to have something `INLINE` on the LHS of a rule, as long as it is unsaturated. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Actually this is already a problem today. It's just rendered more prominent now that even `(:)` has a wrapper. Consider {{{ data T = MkT {-# UNPACK #-} !Int {-# RULES "fT" f MkT = True "gT" forall x. g (MkT x) = x #-} f :: (Int -> T) -> Bool {-# NOINLINE f #-} f x = True g :: T -> Int {-# NOINLINE g #-} g (MkT x) = x+1 }}} yields {{{ Foo.hs:9:1: warning: [-Winline-rule-shadowing] Rule "fT" may never fire because 'Foo.$WMkT' might inline first Probable fix: add an INLINE[n] or NOINLINE[n] pragma for 'Foo.$WMkT' Foo.hs:10:1: warning: [-Winline-rule-shadowing] Rule "gT" may never fire because 'Foo.$WMkT' might inline first Probable fix: add an INLINE[n] or NOINLINE[n] pragma for 'Foo.$WMkT' }}} What to do? If we are to match these rules, we really must delay inlining the wrapper for `MkT` (after inlining we get a mess of unboxing etc). So either we must allow you to add a NOINLINE pragma to `MkT`; or we must add one automatically (e.g. `NOINLINE [1]`). Delaying all consructor-wrapper inlining to phase 1 is potentially quite drastic, because case-of-known-constructor wouldn't happen until the wrappers are inlined. Maybe that's ok; I'm not sure. Worth trying I think. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Well, the whole point of this ticket is to have `ConApp` as soon as possible, and nesting tuples with `$W(,)` will have again the quadratic cost until we get rid of them, so I am not convinced. Also it feels wrong to fight against the inliner here… Would it be wrong for GHC to look a that rule, notice that something marked as `INLINE` occurs on the LHS, but then notice that it is used unsaturated, hence conclude that it will not have been inlined in the program where the rule needs to be matched, and omit the warning? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I have opened #12689 for the issue of rules vs. data con wrappers, as it is a separate one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Plan for #12689: Inline simple wrappers (like the ones that we add here) in the LHS of rules, so that are no worse off than before, and then figure out if we are actually getting the desired improvements with regard to nested tuples (re #5642). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Small update: I have a branch implementing non-compressing `ConApp` that validates and with no significant effect on the program runtimes. And already now, two perf test cases (#9961 and #9233) improved! So there might be something in here for us. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): Cool! I hope to dig into what's been afoot here at hac phi ! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): @nomeata, how much did the benchmarks improve, exactly? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Replying to [comment:32 osa1]:
@nomeata, how much did the benchmarks improve, exactly?
See https://perf.haskell.org/ghc/#revision/1c4c64385bbc315deaff203fbebc423ce79f3...: Weird, the numbers have changed again. 9961 improves by 13%, but 9233 is suddenly missing from the report. Might be a gipeda bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): 13% is great. Can Gipeda show residency too? IIRC at some of the perf tests were causing a lot of trouble not because of allocations but because of residency. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata):
Can Gipeda show residency too?
It could, but does not now. Isn’t residency far too flaky and dependent on flags? I’m very warily of introducing noise from not very helpful tests. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Allright, it is done, and I can report back. Introducing `ConApp` (without any compression) was quite tedious, and for me, rather two than one week. By now, it validates (almost; the GHCi debugger shows some difference in behaviour that I did not investigate) and shows the same runtime performance. The most tricky points are related to rules, which really do not like it if eta-expansion changes the Core too much. It took me a while to get equivalent program output after this refactoring (and I took a shortcut for now, duplicating some list fusion rules that match `build (:)` to have a second variant matching `build (\x y -> x : y)`). With a bit more careful work, this could be fixed, should we want this code to be merged. This change on its own affected some compiler perf benchmarks in the test suite: T9961 improves by 13%, T9233 by 2.5%., T9020 by 2.5%. T4801 regresses by 3.87% (bytes allocated) I then, in a separate patch, implemented omitting redundant type arguments from constructors such as `Just`, `(:)` and tuples, which was the main motivation here. At every use of `ConApp`, I tried to understand the code as to whether it actually cares about the type arguments (which means that the they need to be recovered) or not (in which case the compressed argument list can be traversed, which is of course more efficient). In these places I had to uncompress the type arguments: * `freeVars` (which also calculates the types) * The linter * `cpeRhsE` * `exprIsConApp_maybe` * `exprType` * `collectStaticPtrSatArgs`, `sptModuleInitCode` (all about static pointer tables) * `decomposeRuleLhs` in the desugarer * `toIfaceExpr` when serializing tuples (low-hanging fruit here) * `match_magicDict` * `occAnal` * `simplExprF1` * `isValue` is `specConstr` I found that it is crucial to analyze the type of the data constructor only once, and store the “compression scheme” (i.e. which type arguments to recover form which term arguments) once in the data constructor, as this analysis is not completely cheap. But even with this optimization in place, the effect of this is – neglectible. My gut feeling: * `ConApp` is not a good idea in this form. Constructor applications are still just applications, and treating them that separately is not going to be healthy. It might be a better idea to make ''all'' applications saturated (as in strict core, or less invasive, “spotty types”). * The compression scheme is nice in principle, but there are still too many code paths that want the types. Some might be taken off the list after careful analysis of the code and mild refactoring. In others, making sure that the type in a `Type` data constructor is used as lazily as possible might help avoiding actually running `exprType` (this is a blind guess). * Furthermore, the large types that occur with nested tuples are already in the type checker! So avoiding them in Core is only half the story. * If compression would make a difference, then I think we want it at all applications (or at least applications headed by an `Id`, where we could store the compression scheme). Another point in favor of making all applications saturated. As for the problem of nested tuples: Maybe it would have been better to first carefully analyze the compiler (using `-v`/profiling/ticky-ticky) to be sure where we pay the unwanted cost (type checking, Core, interfaces, somewhere else) to know what we have to fix, before having a shot at one assumed cause. The code is at Phab:D2564. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:36 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12618: Add saturated constructor applications to Core -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I did a full implementation of System IF some years ago, and concluded (like you) that the pain is not worth the gain. Your point that the type checker is building these very big types in the nested-tuple case is an excellent one. I don't have any brilliant ideas, I'm afraid. But this is an excellent data point. Is Phab a good place to keep the patch long-term, or would it be best pushed into the GHC repo? Good work, even if disappointing! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12618#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC