Hello Ghc people,

I have been working on adding support for "derive Functor" to ghc. I have a
patch that mostly works, but there are some problems:


1. Ghc reports the correct instance when I use -ddump-deriv:, but that instance
is not subsequenctly used. Instead I get a warning like:

        Warning: No explicit method nor default method for `fmap'
        In the instance declaration for `Functor (Cont r)'

    What could be going on here? The full output is attached.


2. As far as I understand the code, there would need to be three traversals of a
data type T to derive an instance Functor T:

      - First to determine whether the deriving should be allowed at all
        (checkSideConditions)
      - Then to determine the constraints needed (mk_data_eqn)
      - Finally to make the body of the instance (gen_Functor_binds)

    This seems a bit redundant, and currently the code only does the last pass.
    It would make more sense to report any errors during this pass as well.

    I don't understand how the constraints are determined in TcDeriv, for
    instance for the type

        data T1 a b c = T1 a  deriving (Eq)

    it seems as if Eq constraints are added for all of {a,b,c}, but somehow only
    a constraint Eq a ends up in the final instance. How does that work?



The (experimental) patch was too large to attach, it can be found at http://twan.home.fmf.nl/files/deriv-functor-experimental1.patch.gz


By the way: is there any advantage (besides readability) to generating the code
  "fmap f" instead of "\x -> fmap f x"?


Twan

E:\Dev\ghc\ghc-head3\testsuite\tests\ghc-regress\deriving\should_run>e:\dev\ghc\ghc-head3\ghc\stage1-inplace\ghc
 -c drvrun-functor2.hs -fforce-recomp -ddump-deriv

==================== Derived instances ====================
InstInfo: forall r_aff. GHC.Base.Functor (Main.Cont r_aff)
  { GHC.Base.fmap f_afU (Main.Cont a1_afW)
                    = Main.Cont
                        (\ b1_afY -> a1_afW (\ b2_ag0 -> b1_afY (f_afU 
b2_ag0))) }
InstInfo: forall r_afj w_afk.
          GHC.Base.Functor (Main.ReaderWriter r_afj w_afk)
  { GHC.Base.fmap f_ag4 (Main.RW a1_ag6)
                    = Main.RW
                        (\ b1_ag8
                             -> case a1_ag6 b1_ag8 of {
                                  ((a1_aga, a2_agc)) -> (f_ag4 a1_aga, a2_agc) 
}) }



drvrun-functor2.hs:8:14:
    Warning: No explicit method nor default method for `fmap'
    In the instance declaration for `Functor (ReaderWriter r w)'

drvrun-functor2.hs:11:14:
    Warning: No explicit method nor default method for `fmap'
    In the instance declaration for `Functor (Cont r)'

{-# LANGUAGE DeriveFunctor #-}

module Main where

-- Derive functor for a data type with functions and tuples

data ReaderWriter r w a = RW { runRW :: r -> (a,w) }
    deriving (Functor)

data Cont r a = Cont { runCont :: (a -> r) -> r }
    deriving (Functor)

main = do
    let rw = RW (\r -> ("something",r*3))
    print (runRW rw 123)
    print (runRW (fmap reverse rw) 456)
    let five = Cont ($ 5)
    runCont five print
    runCont (fmap (*2) five) print

data X a = X
instance Functor X where
   fmap _ X = X

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

Reply via email to