[GHC] #10447: DeriveFoldable rejects instances with constraints in last argument of data type

GHC ghc-devs at haskell.org
Tue May 26 00:13:44 UTC 2015


#10447: DeriveFoldable rejects instances with constraints in last argument of data
type
-------------------------------------+-------------------------------------
        Reporter:  RyanGlScott       |                   Owner:
            Type:  bug               |                  Status:  new
        Priority:  normal            |               Milestone:
       Component:  Compiler          |                 Version:  7.10.1
      Resolution:                    |                Keywords:
Operating System:  Unknown/Multiple  |            Architecture:
 Type of failure:  GHC rejects       |  Unknown/Multiple
  valid program                      |               Test Case:
      Blocked By:                    |                Blocking:
 Related Tickets:  #8678             |  Differential Revisions:
-------------------------------------+-------------------------------------
Description changed by RyanGlScott:

Old description:

> Currently, the {{{-XDeriveFoldable}}} extension will reject any derived
> {{{Foldable}}} instance for a data type where the last argument of the
> type constructor is constrained. For example, using this data type from
> [http://git.haskell.org/ghc.git/blob/9f968e97a0de9c2509da00f6337b612dd72a0389:/compiler/typecheck/TcDeriv.hs#l1425
> TcDeriv.hs] as inspiration:
>
> {{{#!hs
> {-# LANGUAGE DeriveFoldable, GADTs, StandaloneDeriving #-}
> module DeriveFoldableRejected where
>
> data T a b where
>     T4 :: Ord b => b -> T a b
>     T5 :: b -> T b b
>     T6 :: T a (b,b)
>
> deriving instance Foldable (T a)
> }}}
>
> Compiling {{{DeriveFoldableRejected.hs}}} with GHC 7.10 will currently
> fail:
>
> {{{
> DeriveFoldableRejected.hs:9:1:
>     Can't make a derived instance of ‘Foldable (T a)’:
>       Constructor ‘T4’ must be truly polymorphic in the last argument of
> the data type
>     In the stand-alone deriving instance for ‘Foldable (T a)’
> Failed, modules loaded: none.
> }}}
>
> I don't think this restriction needs to apply to {{{Foldable}}}
> instances. Unlike {{{Functor}}} and {{{Traversable}}} instances, which
> require the last argument to be truly universal, {{{Foldable}}} instances
> can get away without this. To demonstrate, here's a slightly modified
> {{{T}}} data type, without the constraints:
>
> {{{#!hs
> {-# LANGUAGE DeriveFoldable, GADTs, StandaloneDeriving #-}
> {-# OPTIONS_GHC -ddump-deriv #-}
> module DeriveFoldableLegal where
>
> data T a b where
>     T45 :: b -> T a b
>     T6  :: T a b
>
> deriving instance Foldable (T a)
> }}}
>
> The output of {{{-ddump-deriv}}} is:
>
> {{{
> Derived instances:
>   instance Data.Foldable.Foldable
>              (DeriveFoldableRejected.T a_aDc) where
>     Data.Foldable.foldr f_aDd z_aDe (DeriveFoldableRejected.T45 a1_aDf)
>       = f_aDd a1_aDf z_aDe
>     Data.Foldable.foldr f_aDg z_aDh DeriveFoldableRejected.T6 = z_aDh
>     Data.Foldable.foldMap f_aDi (DeriveFoldableRejected.T45 a1_aDj)
>       = f_aDi a1_aDj
>     Data.Foldable.foldMap f_aDk DeriveFoldableRejected.T6
>       = GHC.Base.mempty
> }}}
>
> Copying this back into {{{DeriveFoldableRejected.hs}}} (after some
> cleanup):
>
> {{{#!hs
> {-# LANGUAGE DeriveFoldable, GADTs, StandaloneDeriving #-}
> module DeriveFoldableRejected where
>
> data T a b where
>     T4 :: Ord b => b -> T a b
>     T5 :: b -> T b b
>     T6 :: T a (b,b)
>
> instance Foldable (T a) where
>     foldr f z (T4 a) = f a z
>     foldr f z (T5 a) = f a z
>     foldr f z T6     = z
>
>     foldMap f (T4 a) = f a
>     foldMap f (T5 a) = f a
>     foldMap f T6     = mempty
> }}}
>
> reveals that it will compile correctly with the generated code.
> Therefore, it seems like the check for universality in the last type
> argument shouldn't be used in {{{-XDeriveFoldable}}}.

New description:

 Currently, the {{{-XDeriveFoldable}}} extension will reject any derived
 {{{Foldable}}} instance for a data type where the last argument of the
 type constructor is constrained. For example, using this data type from
 [http://git.haskell.org/ghc.git/blob/9f968e97a0de9c2509da00f6337b612dd72a0389:/compiler/typecheck/TcDeriv.hs#l1425
 TcDeriv.hs] as inspiration:

 {{{#!hs
 {-# LANGUAGE DeriveFoldable, GADTs, StandaloneDeriving #-}
 module DeriveFoldableRejected where

 data T a b where
     T4 :: Ord b => b -> T a b
     T5 :: b -> T b b
     T6 :: T a (b,b)

 deriving instance Foldable (T a)
 }}}

 Compiling {{{DeriveFoldableRejected.hs}}} with GHC 7.10 will currently
 fail:

 {{{
 DeriveFoldableRejected.hs:9:1:
     Can't make a derived instance of ‘Foldable (T a)’:
       Constructor ‘T4’ must be truly polymorphic in the last argument of
 the data type
     In the stand-alone deriving instance for ‘Foldable (T a)’
 Failed, modules loaded: none.
 }}}

 I don't think this restriction needs to apply to {{{Foldable}}} instances.
 Unlike {{{Functor}}} and {{{Traversable}}} instances, which require the
 last argument to be truly universal, {{{Foldable}}} instances can get away
 without this. To demonstrate, here's a slightly modified {{{T}}} data
 type, without the constraints:

 {{{#!hs
 {-# LANGUAGE DeriveFoldable, GADTs, StandaloneDeriving #-}
 {-# OPTIONS_GHC -ddump-deriv #-}
 module DeriveFoldableLegal where

 data T a b where
     T45 :: b -> T a b
     T6  :: T a b

 deriving instance Foldable (T a)
 }}}

 The output of {{{-ddump-deriv}}} is:

 {{{
 Derived instances:
   instance Data.Foldable.Foldable (DeriveFoldableLegal.T a_aDc) where
     Data.Foldable.foldr f_aDd z_aDe (DeriveFoldableLegal.T45 a1_aDf)
       = f_aDd a1_aDf z_aDe
     Data.Foldable.foldr f_aDg z_aDh DeriveFoldableLegal.T6 = z_aDh
     Data.Foldable.foldMap f_aDi (DeriveFoldableLegal.T45 a1_aDj)
       = f_aDi a1_aDj
     Data.Foldable.foldMap f_aDk DeriveFoldableLegal.T6
       = GHC.Base.mempty
 }}}

 Copying this back into {{{DeriveFoldableRejected.hs}}} (after some
 cleanup):

 {{{#!hs
 {-# LANGUAGE DeriveFoldable, GADTs, StandaloneDeriving #-}
 module DeriveFoldableRejected where

 data T a b where
     T4 :: Ord b => b -> T a b
     T5 :: b -> T b b
     T6 :: T a (b,b)

 instance Foldable (T a) where
     foldr f z (T4 a) = f a z
     foldr f z (T5 a) = f a z
     foldr f z T6     = z

     foldMap f (T4 a) = f a
     foldMap f (T5 a) = f a
     foldMap f T6     = mempty
 }}}

 reveals that it will compile correctly with the generated code. Therefore,
 it seems like the check for universality in the last type argument
 shouldn't be used in {{{-XDeriveFoldable}}}.

--

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


More information about the ghc-tickets mailing list