On Fri, Dec 21, 2012 at 10:12:38AM +0000, Simon Peyton-Jones wrote: > I would not use -XMonoLocalBinds for all modules -- that will force you to do > more work. > Instead use it just for the offending Pol3_ module, via {-# LANGUAGE > MonoLocalBinds #-} > > Or, probably better, give a type signature inside moduloBasisx, as suggested > in the http://hackage.haskell.org/trac/ghc/ticket/4361. The signature is > better because it also makes the program easier to understand! > > Simon > > [..]
> | > * Alterantively, give a type signature for x, thus (in this case) > | > > | > moduloBasisx p = let x :: () > | > x = upLinSolvRing p > | > in () Now, I am trying ghc-7.6.1.20121207 built from source on Debian Linux. -- 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 -- new -O --------------------------------------------------------------- `make build' fails at Pol3_.hs, at compiling this instance -- Pol3_.hs ---------------------------------------------------- ... {-# LANGUAGE ScopedTypeVariables #-} -- (1) ** instance forall a. (LinSolvRing (Pol a), CommutativeRing a) => -- (2) ** LinSolvRing (UPol (Pol a)) where -- gxBasis in P[y], P = a[x1..xn]. -- Map to a[y,x1..xn] apply gxBasis there, return to P: 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 -- (3) ** dP' :: forall a. (LinSolvRing (Pol a), CommutativeRing a) => -- (4) ** Domains1 (Pol a) dP' = upLinSolvRing p' Map.empty -- p needs lexPPO reordering, then, -- its domain bundle needs change too s' = cToUPol y dP' p' -- sample for P'[y], P' = a[x1..xn] with lexComp toOverP' = ct s' . map (\ (a, j) -> (toLex a, j)) . upolMons fromOverP' = ct f . map (\ (a, j) -> (fromLex a, j)) . upolMons -- P[y] <--> P'[y] back = fromOverP' . headVarPol dP (gs, mt) = gxBasis $ map (fromHeadVarPol . toOverP') fs ----------------------------------------------------------------- What is newly added: 1) -XRankNTypes to docon.cabal -- in order to allow `forall' to `instance'. 2) {-# LANGUAGE ScopedTypeVariables #-} -- to support explicit polymorphic type signatures in the instance implementation, 3) asTypeOf for p', 4) Explicit signature for dP'. The report is similar as the old one: ------------------------------------------------ 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:17 `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' ------------------------------------------------------------- ghc-7.4.1 compiles everything without additions. Can you, please, advise about options in docon.cabal, where to set `forall a', signatures, etc ? Regards, ------ Sergei _______________________________________________ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs