On Fri, Dec 21, 2012 at 11:26:30AM +0000, Simon Peyton-Jones wrote: > I think you need to remove the 'forall a' on the type signature for dP'. > The 'a' you mean is the 'a' from the instance declaration, not a > completely fresh 'a'.
This looks reasonable. > Moreover I don't think you need the 'forall' on the 'instance' declaration. > Just 'ScopedTypeVariables' should do it All right, I try to follow both instructions: -- docon.cabal ----------------------------------------------------- ... extensions: TypeSynonymInstances UndecidableInstances FlexibleContexts FlexibleInstances MultiParamTypeClasses OverlappingInstances RecordWildCards NamedFieldPuns DoAndIfThenElse . ghc-options: -fno-warn-overlapping-patterns -fwarn-unused-binds -fwarn-unused-matches -fwarn-unused-imports -XRankNTypes -- ** probably, it spoils nothing -O --------------------------------------------------------------- -- Pol3_.hs ---------------------------------------------------- ... {-# LANGUAGE ScopedTypeVariables #-} -- (1) ** instance (LinSolvRing (Pol a), CommutativeRing a) => LinSolvRing (UPol (Pol a)) where gxBasis [] = ([], []) gxBasis fs@(f:_) = (map back gs, mapmap back mt) where UPol _ p y dP = f (o, n) = (pPPO p, genLength $ pVars p) (toLex, fromLex) = (reordPol $ lexPPO n, reordPol o) p' = (toLex p) `asTypeOf` p -- (2) ** dP' :: (LinSolvRing (Pol a), CommutativeRing a) => -- (3) ** Domains1 (Pol a) dP' = upLinSolvRing p' Map.empty s' = cToUPol y dP' p' toOverP' = ct s' . map (\ (a, j) -> (toLex a, j)) . upolMons fromOverP' = ct f . map (\ (a, j) -> (fromLex a, j)) . upolMons back = fromOverP' . headVarPol dP (gs, mt) = gxBasis $ map (fromHeadVarPol . toOverP') fs ----------------------------------------------------------------- This does not help: --------------------------------------------------------- Pol3_.hs:328:25: Could not deduce (a ~ a1) from the context (CommutativeRing (UPol (Pol a)), MulMonoid (UPol (Pol a)), LinSolvRing (Pol a), CommutativeRing a) bound by the instance declaration at Pol3_.hs:(313,10)-(314,72) or from (LinSolvRing (Pol a1), CommutativeRing a1) bound by the type signature for dP' :: (LinSolvRing (Pol a1), CommutativeRing a1) => Domains1 (Pol a1) at Pol3_.hs:327:12-71 `a' is a rigid type variable bound by the instance declaration at Pol3_.hs:313:10 `a1' is a rigid type variable bound by the type signature for dP' :: (LinSolvRing (Pol a1), CommutativeRing a1) => Domains1 (Pol a1) at Pol3_.hs:327:12 Expected type: Pol a1 Actual type: Pol a In the first argument of `upLinSolvRing', namely p' In the expression: upLinSolvRing p' Map.empty In an equation for dP': dP' = upLinSolvRing p' Map.empty Pol3_.hs:331:20: Could not deduce (EuclideanRing a) arising from a use of dP' from the context (CommutativeRing (UPol (Pol a)), MulMonoid (UPol (Pol a)), LinSolvRing (Pol a), CommutativeRing a) bound by the instance declaration at Pol3_.hs:(313,10)-(314,72) Possible fix: add (EuclideanRing a) to the context of the instance declaration In the second argument of `cToUPol', namely dP' In the expression: cToUPol y dP' p' In an equation for s': s' = cToUPol y dP' p' ---------------------------------------------------------- Regards, ------ Sergei _______________________________________________ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs