#5227: Large space usage when deriving Generic
---------------------------------+------------------------------------------
    Reporter:  igloo             |        Owner:  jpm@…       
        Type:  bug               |       Status:  new         
    Priority:  high              |    Milestone:  7.2.1       
   Component:  Compiler          |      Version:  7.1         
    Keywords:                    |     Testcase:              
   Blockedby:                    |   Difficulty:              
          Os:  Unknown/Multiple  |     Blocking:              
Architecture:  Unknown/Multiple  |      Failure:  None/Unknown
---------------------------------+------------------------------------------

Comment(by simonpj):

 * We only derive Eq, Ord etc for tuples up to 15-tuples (see `GHC.Base`)
 and Data for tuples up to 7-tuples.  I think it would be reasonable to
 derive `Generic` only up to 7-tuples.  Could you try that?

  * I'm guessing (but I have not checked) that a big reason for the blow-up
 is the repetition of type arguments; see http://research.microsoft.com/en-
 us/um/people/simonpj/papers/variant-f/if.pdf, page 5.  Indeed Section 2.3
 explicitly mentions the derivable-type-classes stuff as provoking the bad
 behaviour.

  * The paper mentions a quadratic blow-up, but I think it's actually only
 N*logN if the tuples are balanced.  But the constant factor seems large:
 see the example below.

  * At the moment every derived instance is totally independent of every
 other one.  But there must be a lot of repetition.  Could we generate more
 compact code by hand-writing the derived tuple instances?

 For this innocent triple:
 {{{
 data T = MkT Int Int Int deriving( Generic )
 }}}
 we get the following "from" function (omitting all type info):
 {{{
 ghc -c -XDeriveGeneric Foo.hs -ddump-simpl -dsuppress-all
 ...
 $cfrom_rjE =
   \ (@ x_af9) (ds_dj5 :: T) ->
     case ds_dj5 of _ { MkT g1_af0 g2_af1 g3_af2 ->
     (:*:
        (g1_af0 `cast` ...) (:*: (g2_af1 `cast` ...) (g3_af2 `cast` ...)))
     `cast` ...
     }
 }}}
 Seems reasonable.  But show the type info and it looks like this:
 {{{
 $cfrom_rjE :: forall x_af8. Foo.T -> GHC.Generics.Rep Foo.T x_af8
 [GblId, Arity=1, Caf=NoCafRefs]
 $cfrom_rjE =
   \ (@ x_af9) (ds_dj5 :: Foo.T) ->
     case ds_dj5 of _ { Foo.MkT g1_af0 g2_af1 g3_af2 ->
     (GHC.Generics.:*:
        @ (GHC.Generics.M1
             GHC.Generics.S
             GHC.Generics.NoSelector
             (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int))
        @ (GHC.Generics.M1
             GHC.Generics.S
             GHC.Generics.NoSelector
             (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
           GHC.Generics.:*: GHC.Generics.M1
                              GHC.Generics.S
                              GHC.Generics.NoSelector
                              (GHC.Generics.K1 GHC.Generics.R
 GHC.Types.Int))
        @ x_af9
        (g1_af0
         `cast` (Sym
                   (GHC.Generics.NTCo:K1
                      <GHC.Generics.R> <GHC.Types.Int> <x_af9>) ; Sym
 (GHC.Generics.NTCo:M1
 <GHC.Generics.S>
 <GHC.Generics.NoSelector>
 <GHC.Generics.K1
 GHC.Generics.R
 GHC.Types.Int>) <x_af9>
                 :: GHC.Types.Int
                      ~
                    GHC.Generics.M1
                      GHC.Generics.S
                      GHC.Generics.NoSelector
                      (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
                      x_af9))
        (GHC.Generics.:*:
           @ (GHC.Generics.M1
                GHC.Generics.S
                GHC.Generics.NoSelector
                (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int))
           @ (GHC.Generics.M1
                GHC.Generics.S
                GHC.Generics.NoSelector
                (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int))
           @ x_af9
           (g2_af1
            `cast` (Sym
                      (GHC.Generics.NTCo:K1
                         <GHC.Generics.R> <GHC.Types.Int> <x_af9>) ; Sym
 (GHC.Generics.NTCo:M1
 <GHC.Generics.S>
 <GHC.Generics.NoSelector>
 <GHC.Generics.K1
 GHC.Generics.R
 GHC.Types.Int>) <x_af9>
                    :: GHC.Types.Int
                         ~
                       GHC.Generics.M1
                         GHC.Generics.S
                         GHC.Generics.NoSelector
                         (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
                         x_af9))
           (g3_af2
            `cast` (Sym
                      (GHC.Generics.NTCo:K1
                         <GHC.Generics.R> <GHC.Types.Int> <x_af9>) ; Sym
 (GHC.Generics.NTCo:M1
 <GHC.Generics.S>
 <GHC.Generics.NoSelector>
 <GHC.Generics.K1
 GHC.Generics.R
 GHC.Types.Int>) <x_af9>
                    :: GHC.Types.Int
                         ~
                       GHC.Generics.M1
                         GHC.Generics.S
                         GHC.Generics.NoSelector
                         (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
                         x_af9))))
     `cast` (Sym
               (GHC.Generics.NTCo:M1
                  <GHC.Generics.C>
                  <Foo.C1_0T>
                  <GHC.Generics.M1
                     GHC.Generics.S
                     GHC.Generics.NoSelector
                     (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
                   GHC.Generics.:*: (GHC.Generics.M1
                                       GHC.Generics.S
                                       GHC.Generics.NoSelector
                                       (GHC.Generics.K1 GHC.Generics.R
 GHC.Types.Int)
                                     GHC.Generics.:*: GHC.Generics.M1
                                                        GHC.Generics.S
 GHC.Generics.NoSelector
                                                        (GHC.Generics.K1
                                                           GHC.Generics.R
 GHC.Types.Int))>) ; (Sym
 (GHC.Generics.NTCo:M1
 <GHC.Generics.D>
 <Foo.D1T>
 <GHC.Generics.M1
 GHC.Generics.C
 Foo.C1_0T
 (GHC.Generics.M1
 GHC.Generics.S
 GHC.Generics.NoSelector
 (GHC.Generics.K1
 GHC.Generics.R
 GHC.Types.Int)
 GHC.Generics.:*: (GHC.Generics.M1
 GHC.Generics.S
 GHC.Generics.NoSelector
 (GHC.Generics.K1
 GHC.Generics.R
 GHC.Types.Int)
 GHC.Generics.:*: GHC.Generics.M1
 GHC.Generics.S
 GHC.Generics.NoSelector
 (GHC.Generics.K1
 GHC.Generics.R
 GHC.Types.Int)))>) ; Sym
 (Foo.TFCo:Rep_T)) <x_af9>
             :: (GHC.Generics.:*:)
                  (GHC.Generics.M1
                     GHC.Generics.S
                     GHC.Generics.NoSelector
                     (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int))
                  (GHC.Generics.M1
                     GHC.Generics.S
                     GHC.Generics.NoSelector
                     (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
                   GHC.Generics.:*: GHC.Generics.M1
                                      GHC.Generics.S
                                      GHC.Generics.NoSelector
                                      (GHC.Generics.K1 GHC.Generics.R
 GHC.Types.Int))
                  x_af9
                  ~
                GHC.Generics.Rep Foo.T x_af9)
     }
 }}}
 Lots and lots of repeated types.  And that's for a triple.  Try a
 10-tuple!

 I don't really have a good way to solve this, except by using System IF
 (the paper) or perhaps by let-binding types which would be a significant
 change.

 '''Short term: just up to 7-tuples, like Data.'''

 Simon

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5227#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to