[GHC] #8914: Remove unnecessary constraints from MonadComprehensions and ParallelListComp

GHC ghc-devs at haskell.org
Wed Mar 19 16:29:33 UTC 2014


#8914: Remove unnecessary constraints from MonadComprehensions and
ParallelListComp
-------------------------------------------+-------------------------------
       Reporter:  Iceland_jack             |             Owner:
           Type:  feature request          |            Status:  new
       Priority:  normal                   |         Milestone:
      Component:  Compiler (Type checker)  |           Version:
       Keywords:                           |  Operating System:
   Architecture:  Unknown/Multiple         |  Unknown/Multiple
     Difficulty:  Difficult (2-5 days)     |   Type of failure:
     Blocked By:                           |  None/Unknown
Related Tickets:                           |         Test Case:
                                           |          Blocking:
-------------------------------------------+-------------------------------
 Many parts of MonadComprehensions don't actually require monads instance,
 the following could do with a `Functor` constraint
 {{{
 fmapM :: Monad m => (a -> b) -> m a -> m b
 fmapM f xs = [ f x | x <- xs ]
 }}}

 and I don't see any reason why the class `MonadZip` (from
 [http://hackage.haskell.org/package/base-4.4.0.0/docs/Control-Monad-
 Zip.html Control.Monad.Zip]) requires a `Monad` constraint rather a
 `Functor` constraint:

 {{{
 class Functor f => FunctorZip f where
     fzip :: f a -> f b -> f (a,b)
     fzip = fzipWith (,)

     fzipWith :: (a -> b -> c) -> f a -> f b -> f c
     fzipWith f fa fb = fmap (uncurry f) (fzip fa fb)

     funzip :: f (a,b) -> (f a, f b)
     funzip fab = (fmap fst fab, fmap snd fab)
 }}}

 with the laws
 {{{
     fmap (f *** g) (fzip fa fb) = fzip (fmap f fa) (fmap g fb)

     fmap (const ()) fa = fmap (const ()) fb
 ==> funzip (fzip fa fb) = (fa, fb)
 }}}

 Same with `Applicative` (see ApplicativeDo):
 {{{
 liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
 liftA2 f a1 a2 = [ f x1 x2 | x1 <- a1, x2 <- a2 ]
 }}}

 The reason I bring this up is because I'm writing a DSL that uses length-
 indexed vectors whose `Functor` and `FunctorZip` instances are trivial but
 whose `Monad` instance is [http://stackoverflow.com/questions/5802628
 /monad-instance-of-a-number-parameterised-vector complicated] and not
 need.

 This proposal shares a similar rationale as ApplicativeDo.

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


More information about the ghc-tickets mailing list